From: Ron Garret
Subject: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-1B89E6.21422911072006@news.gha.chartermi.net>
What should (ignore-errors ((foo))) do?

If you think it should return NIL, what should (compile nil (lambda () 
(ignore-errors ((foo))))) do?

And in case you're wondering why I'm asking, I want to define a macro 
that works just like FUNCTION except that if FUNCTION would return an 
error it does some special processing, i.e. something like:

(defmacro my-function (thing)
  `(or (ignore-errors (function, thing)) (special-processing thing))))

I've tried this in ACL and MCL, and it doesn't work in either one.  Both 
generate compiler errors for e.g. (my-function ignore-errors).

rg

From: ······@gmail.com
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152687665.930906.212300@m79g2000cwm.googlegroups.com>
Ron Garret wrote:
> What should (ignore-errors ((foo))) do?
>
> If you think it should return NIL, what should (compile nil (lambda ()
> (ignore-errors ((foo))))) do?
>
> And in case you're wondering why I'm asking, I want to define a macro
> that works just like FUNCTION except that if FUNCTION would return an
> error it does some special processing, i.e. something like:
>
> (defmacro my-function (thing)
>   `(or (ignore-errors (function, thing)) (special-processing thing))))
>
> I've tried this in ACL and MCL, and it doesn't work in either one.  Both
> generate compiler errors for e.g. (my-function ignore-errors).
>
> rg


Doesn't a
(if (functionp thing)
    (function thing)
    (special-processing thing))

work?
From: Stefan Mandl
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hjs5jF1rtfodU1@news.dfncis.de>
>> What should (ignore-errors ((foo))) do?

The Hyperspec says:

ignore-errors is used to prevent conditions of type error from causing entry into the debugger.

I guess that ((foo)) is more a syntax error than a runtime condition.

when I try:

---------
(defun square (x) (* x x))
(defmacro my-function (thing)
   `(or (ignore-errors (square ,thing)) (format t "square failed for ~a" (quote ,thing))))
---------

it seems to work just fine:

CL-USER> (my-function 3)
9
CL-USER> (let ((a 3)) (my-function (+ a (incf a) a)))
121
CL-USER> (my-function (+ 3 "a"))
square failed for (+ 3 a)
NIL


regards,
Stefan
From: Pascal Bourguignon
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <87odvu1yxl.fsf@thalassa.informatimago.com>
Stefan Mandl <············@informatik.uni-erlangen.de> writes:

>>> What should (ignore-errors ((foo))) do?
>
> The Hyperspec says:
>
> ignore-errors is used to prevent conditions of type error from
> causing entry into the debugger.
>
> I guess that ((foo)) is more a syntax error than a runtime condition.

Yes, but PROGRAM-ERROR is a subclass of ERROR.


-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

Nobody can fix the economy.  Nobody can be trusted with their finger
on the button.  Nobody's perfect.  VOTE FOR NOBODY.
From: Stefan Mandl
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hl2geF3v5dU1@news.dfncis.de>
Pascal Bourguignon wrote:
> Stefan Mandl <············@informatik.uni-erlangen.de> writes:
> 
>>>> What should (ignore-errors ((foo))) do?
>> The Hyperspec says:
>>
>> ignore-errors is used to prevent conditions of type error from
>> causing entry into the debugger.
>>
>> I guess that ((foo)) is more a syntax error than a runtime condition.
> 
> Yes, but PROGRAM-ERROR is a subclass of ERROR.

Ahh, I see -- thanks.

--
Stefan.
From: Pascal Costanza
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hl5kuF4gg7U1@individual.net>
Pascal Bourguignon wrote:
> Stefan Mandl <············@informatik.uni-erlangen.de> writes:
> 
>>>> What should (ignore-errors ((foo))) do?
>> The Hyperspec says:
>>
>> ignore-errors is used to prevent conditions of type error from
>> causing entry into the debugger.
>>
>> I guess that ((foo)) is more a syntax error than a runtime condition.
> 
> Yes, but PROGRAM-ERROR is a subclass of ERROR.

PROGRAM-ERROR does not explicitly apply to forms like ((foo)). 3.1.2.1.2 
simply says that when the car of a cons is not a symbol, that car must 
be a lambda expression. It doesn't say anything about errors.

I guess this is just underspecified.


Pascal

-- 
3rd European Lisp Workshop
July 3 - Nantes, France - co-located with ECOOP 2006
http://lisp-ecoop06.bknr.net/
From: Marcus Breiing
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <e93oj9$nq7$1@chessie.cirr.com>
Pascal Costanza <··@p-cos.net> writes:

> I guess this is just underspecified.

Well, it is non-conforming code after all (I think:-)

Here's a somewhat similar case:

(defmacro foo ()
  (error "barf!"))

Now what should

  (ignore-errors (foo))

return?

I wouldn't complain if an interpreter were to return NIL.

On the other hand, since (foo) can't be macroexpanded without error,
it seems to follow that the whole can't be even "minimally" compiled
without error.

-- 
Marcus Breiing
From: Nathan Baum
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152745609.531769.291420@h48g2000cwc.googlegroups.com>
Marcus Breiing wrote:
> Pascal Costanza <··@p-cos.net> writes:
>
> > I guess this is just underspecified.
>
> Well, it is non-conforming code after all (I think:-)
>
> Here's a somewhat similar case:
>
> (defmacro foo ()
>   (error "barf!"))
>
> Now what should
>
>   (ignore-errors (foo))
>
> return?
>
> I wouldn't complain if an interpreter were to return NIL.
>
> On the other hand, since (foo) can't be macroexpanded without error,
> it seems to follow that the whole can't be even "minimally" compiled
> without error.

However,

  (ignore-errors (foo))

doesn't _necessarily_ involve compilation. _Some_ implementations may
choose to compile the fragment before executing it, whilst others may
choose to expand the macro later, when ignore-errors will ignore the
condition.

CLISP appears to expand (foo) before the form is executed. The
condition is not ignored and execution fails.

SBCL expands (foo) before the form is executed, but saves the condition
and resignals it when (foo) is actually executed. The condition is
therefore ignored.

  (defmacro foo ()
    (format t "expanding~%")
    (error "foo"))

  (handler-case
   (progn
          (format t "executing~%")
          (foo))
   (condition (c) (format t "caught condition: ~S~%" c)))

  (format t "done~%")

  (quit)

I used this code so I could see what happens more clearly.

CLISP prints:

  expanding
  *** - foo

SBCL prints:

  expanding
  ;     (FOO)
  ;
  ; caught ERROR:
  ;   (in macroexpansion of (FOO))
  ;   (hint: For more precise location, try *BREAK-ON-SIGNALS*.)
  ;   foo

  ;     (SB-KERNEL:FLOAT-WAIT)
  ;
  ; note: deleting unreachable code
  ;
  ; note: deleting unreachable code
  ;
  ; compilation unit finished
  ;   caught 1 ERROR condition
  ;   printed 2 notes
  executing
  caught condition: #<SB-INT:COMPILED-PROGRAM-ERROR {9087F19}>
  done

IMO, SBCL does the right thing. The form is never explicitly compiled,
so even though it _is_ partially compiled, it behaves as though it is
not.

On the other hand, given

  (defun func () (foo))
  (compile 'func)
  (func)

SBCL does't signal an error until the second line, even though compile
is _required_ to have expanded (foo). It does actually expand (foo),
and it prints the error notification, but as before it keeps it until
the code is executed.

That doesn't really make sense to me since the macro _must_ have been
expanded, so there's no obvious point pretending otherwise. Also, the
condition is resignalled each time the function is called, which just
seems to be wrong, particularly considering the _other_ functions in
the macro with side effects are not reevaluated each time the function
is called.

CLISP signals at the defun.

> -- 
> Marcus Breiing
From: ········@tochka.ru
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152758715.850785.57540@b28g2000cwb.googlegroups.com>
Hello,

Nathan Baum wrote:

>   (ignore-errors (foo))
>
> doesn't _necessarily_ involve compilation. _Some_ implementations may
> choose to compile the fragment before executing it, whilst others may
> choose to expand the macro later, when ignore-errors will ignore the
> condition.
>
> CLISP appears to expand (foo) before the form is executed. The
> condition is not ignored and execution fails.
>
> SBCL expands (foo) before the form is executed, but saves the condition
> and resignals it when (foo) is actually executed. The condition is
> therefore ignored.

Not quite. SBCL compiler catches errors, signalled at compile-time,
replaces uncompilable code with a call to ERROR with *it's own*
condition and returns a flag of error presence:

* (defmacro foo ()
  (format t "expanding~%")
  (error "foo"))

FOO
* (compile nil '(lambda (x) (if x (list x) (foo))))
expanding
; in: LAMBDA (X)
;     (FOO)
;
; caught ERROR:
;   (in macroexpansion of (FOO))
;   (hint: For more precise location, try *BREAK-ON-SIGNALS*.)
;   foo
;
; compilation unit finished
;   caught 1 ERROR condition
#<FUNCTION {AE3FE45}>
T
T
* (funcall * 4)

(4)
* (funcall ** nil)

debugger invoked on a SB-INT:COMPILED-PROGRAM-ERROR:
  Execution of a form compiled with errors.
Form:
  (FOO)
Compile-time error:
  (in macroexpansion of (FOO))
(hint: For more precise location, try *BREAK-ON-SIGNALS*.)
foo

> (defun func () (foo))
>   (compile 'func)
>   (func)
>
> SBCL does't signal an error until the second line,

third?

> even though compile
> is _required_ to have expanded (foo). It does actually expand (foo),

Well, SBCL is a compiler-only implementation, so one argument COMPILE
has no effect--FUNC is already compiled after the first line.

> and it prints the error notification, but as before it keeps it until
> the code is executed.
>
> That doesn't really make sense to me since the macro _must_ have been
> expanded, so there's no obvious point pretending otherwise.

The idea is that the compiler should not fail and ask a manual
intervention on bad code--it should print an error message and
proceed. And a macro, signalling an error, is considered to be just a
sign of a bad code.

> Also, the
> condition is resignalled each time the function is called,

No. When the function is called an error telling "the code was broken
and has not been compiled" is signalled.

--
Regards,
Alexey Dejneka

"Alas, the spheres of truth are less transparent than those of
illusion." -- L.E.J. Brouwer
From: Nathan Baum
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152824029.608191.183120@m73g2000cwd.googlegroups.com>
········@tochka.ru wrote:
> Hello,
>
> Nathan Baum wrote:
>
> >   (ignore-errors (foo))
> >
> > doesn't _necessarily_ involve compilation. _Some_ implementations may
> > choose to compile the fragment before executing it, whilst others may
> > choose to expand the macro later, when ignore-errors will ignore the
> > condition.
> >
> > CLISP appears to expand (foo) before the form is executed. The
> > condition is not ignored and execution fails.
> >
> > SBCL expands (foo) before the form is executed, but saves the condition
> > and resignals it when (foo) is actually executed. The condition is
> > therefore ignored.
>
> Not quite. SBCL compiler catches errors, signalled at compile-time,
> replaces uncompilable code with a call to ERROR with *it's own*
> condition and returns a flag of error presence:

It's obvious now that you point it out. I was seeing "foo" in the error
report and assuming it was the same error.

> > (defun func () (foo))
> >   (compile 'func)
> >   (func)
> >
> > SBCL does't signal an error until the second line,
>
> third?

Yes, I meant third.

>
> > even though compile
> > is _required_ to have expanded (foo). It does actually expand (foo),
>
> Well, SBCL is a compiler-only implementation, so one argument COMPILE
> has no effect--FUNC is already compiled after the first line.

Point being I would fully expect the error to be signalled _upon
compilation_. I'd actually expect an error on the first line, and I'd
expect _any_ implementation to have signalled an error by line two.
There might be a case for keeping the signal back until explicit
compilation has occured; that could improve portability between
implementations that compile implicitly and those that don't.

> > and it prints the error notification, but as before it keeps it until
> > the code is executed.
> >
> > That doesn't really make sense to me since the macro _must_ have been
> > expanded, so there's no obvious point pretending otherwise.
>
> The idea is that the compiler should not fail and ask a manual
> intervention on bad code--it should print an error message and
> proceed. And a macro, signalling an error, is considered to be just a
> sign of a bad code.

I don't think that's very sensible. It may make sense not to break on
"bad code which isn't actually executed at compile time". e.g.
compiling (/ 1 0) needn't break, because the division by zero error
hasn't actually occured yet; a warning is more appropriate. But
explicitly compiling (foo) _necessarily_ results in an error at
compile-time, because the compiler is _required_ to expand the macro.

If I wanted a macro to expand into something which only caused an error
at execution time, I'd explicitly have it expand to a signalling form
of some variety.
From: Juho Snellman
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <slrnebdgum.mrk.jsnell@sbz-30.cs.Helsinki.FI>
Nathan Baum <···········@btinternet.com> wrote:
> Point being I would fully expect the error to be signalled _upon
> compilation_. I'd actually expect an error on the first line, and I'd
> expect _any_ implementation to have signalled an error by line two.

I don't think you should be expecting that. The standard explicitly
allows COMPILE and COMPILE-FILE to do it's own handling of ERRORs:

  compile is permitted, but not required, to establish a handler for
  conditions of type error. For example, the handler might issue a
  warning and restart compilation from some implementation-dependent
  point in order to let the compilation proceed without manual
  intervention.
  
With the only constraint being on the return values:
   
  The tertiary value, failure-p, is false if no conditions of type
  error or warning (other than style-warning) were detected by the
  compiler, and true otherwise.

-- 
Juho Snellman
From: Nathan Baum
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152831873.542635.277670@p79g2000cwp.googlegroups.com>
Juho Snellman wrote:
> Nathan Baum <···········@btinternet.com> wrote:
> > Point being I would fully expect the error to be signalled _upon
> > compilation_. I'd actually expect an error on the first line, and I'd
> > expect _any_ implementation to have signalled an error by line two.
>
> I don't think you should be expecting that. The standard explicitly
> allows COMPILE and COMPILE-FILE to do it's own handling of ERRORs:

Well that kinda sucks, but okay.

On further reflection I think SBCL does the right thing, given the
limitations imposed by the standard.

Consider:

  (defmacro foo ()
    (error "foo"))

On CLISP and SBCL,

  (when nil
    (foo))

both correctly (IMHO) return NIL. SBCL issues a notice of a compilation
error, but the failure of (foo) to expand doesn't actually prevent the
form being evaluated, so it is right not to abort compilation. CLISP
doesn't have to do anything special, it just never expands (foo).

But

  (ignore-errors
    (when nil
      (foo)))

is different. SBCL again issues a notice, but again the failure of
(foo) to expand doesn't prevent the form being evaluated. CLISP,
however, signals an error and execution fails. In CLISP, ignore-errors
appears to force complete macro expansion of its argument.

It may be noted that

  (when nil
    (ignore-errors
      (foo)))

works on CLISP, because ignore-errors is never executed, so (foo) is
never force-expanded.
From: Rob Warnock
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <ybqdnU_r9qaXDyjZnZ2dnUVZ_qudnZ2d@speakeasy.net>
Marcus Breiing  <······@2006w27.mail.breiing.com> wrote:
+---------------
| Here's a somewhat similar case:
| (defmacro foo () (error "barf!"))
| Now what should
|   (ignore-errors (foo))
| return?
| I wouldn't complain if an interpreter were to return NIL.
+---------------

Here might be a good place to point out that IGNORE-ERRORS
returns *two* values when there was an exceptional situation,
with the second one being the condition which error'd, thus
providing a way to distinguish a successful NIL result from
the form...


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Juho Snellman
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <slrnebauik.3gl.jsnell@sbz-30.cs.Helsinki.FI>
Marcus Breiing <······@2006w27.mail.breiing.com> wrote:
> (defmacro foo ()
>   (error "barf!"))
> 
> Now what should
> 
>   (ignore-errors (foo))
> 
> return?
> 
> I wouldn't complain if an interpreter were to return NIL.
> 
> On the other hand, since (foo) can't be macroexpanded without error,
> it seems to follow that the whole can't be even "minimally" compiled
> without error.

Sure it can, since minimal compilation just requires that the macro is
expanded in a way that prevents it from being expanded again at
run-time. For example, the implementation could do as CMUCL and SBCL
do, and install a handler for ERROR around the compilation, which
will:

  * Report the error to the user
  * Signal a new condition, e.g. COMPILER-ERROR, which users can handle
    in their own code, if they have special needs
  * Replace the form that caused the error with a run-time call to
    ERROR
  * Ensure that the FAILURE-P return value of COMPILE / COMPILE-FILE will
    be T

Everybody wins! Even Joe, who wanted both for the compiler to tell
when it finds bogus code, and EVAL being transparent.

* (compile nil '(lambda (x) (if x ((foo)) t)))
; in: LAMBDA (X)
;     ((FOO))
; 
; caught ERROR:
;   illegal function call
; 
; compilation unit finished
;   caught 1 ERROR condition

#<FUNCTION {AD91FD5}>
T
T
* (setf (symbol-function 'foo) *)

#<FUNCTION {AD91FD5}>
* (foo nil)

T
* (foo t)

debugger invoked on a SB-INT:COMPILED-PROGRAM-ERROR:
  Execution of a form compiled with errors.
Form:
  ((FOO))
Compile-time-error:
  illegal function call
restarts (invokable by number or by possibly-abbreviated name):
  0: [ABORT] Exit debugger, returning to top level.

-- 
Juho Snellman
From: Pascal Bourguignon
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <87psgazd9f.fsf@thalassa.informatimago.com>
Marcus Breiing <······@2006w27.mail.breiing.com> writes:

> Pascal Costanza <··@p-cos.net> writes:
>
>> I guess this is just underspecified.
>
> Well, it is non-conforming code after all (I think:-)
>
> Here's a somewhat similar case:
>
> (defmacro foo ()
>   (error "barf!"))
>
> Now what should
>
>   (ignore-errors (foo))
>
> return?
>
> I wouldn't complain if an interpreter were to return NIL.
>
> On the other hand, since (foo) can't be macroexpanded without error,
> it seems to follow that the whole can't be even "minimally" compiled
> without error.

Indeed, with compilers, (ignore-errors (foo)) is dubious.
But: (ignore-errors (compile nil (lambda () (ignore-errors (foo)))))
should work and return NIL, IMO.

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

ADVISORY: There is an extremely small but nonzero chance that,
through a process known as "tunneling," this product may
spontaneously disappear from its present location and reappear at
any random place in the universe, including your neighbor's
domicile. The manufacturer will not be responsible for any damages
or inconveniences that may result.
From: Ron Garret
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-BD179A.12252512072006@news.gha.chartermi.net>
In article <························@m79g2000cwm.googlegroups.com>,
 ······@gmail.com wrote:

> Ron Garret wrote:
> > What should (ignore-errors ((foo))) do?
> >
> > If you think it should return NIL, what should (compile nil (lambda ()
> > (ignore-errors ((foo))))) do?
> >
> > And in case you're wondering why I'm asking, I want to define a macro
> > that works just like FUNCTION except that if FUNCTION would return an
> > error it does some special processing, i.e. something like:
> >
> > (defmacro my-function (thing)
> >   `(or (ignore-errors (function, thing)) (special-processing thing))))
> >
> > I've tried this in ACL and MCL, and it doesn't work in either one.  Both
> > generate compiler errors for e.g. (my-function ignore-errors).
> >
> > rg
> 
> 
> Doesn't a
> (if (functionp thing)
>     (function thing)
>     (special-processing thing))
> 
> work?

Nope.  It would have to be (or (functionp thing) (symbolp thing) (and 
(consp thing) (eq (car thing) 'lambda)))

and even that has cases where it would work (like '(lambda)).

rg
From: ········@gmail.com
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152719137.340967.60030@s13g2000cwa.googlegroups.com>
Ron Garret wrote:
> What should (ignore-errors ((foo))) do?
>
> If you think it should return NIL, what should (compile nil (lambda ()
> (ignore-errors ((foo))))) do?
>
> And in case you're wondering why I'm asking, I want to define a macro
> that works just like FUNCTION except that if FUNCTION would return an
> error it does some special processing, i.e. something like:
>
> (defmacro my-function (thing)
>   `(or (ignore-errors (function, thing)) (special-processing thing))))
>
> I've tried this in ACL and MCL, and it doesn't work in either one.  Both
> generate compiler errors for e.g. (my-function ignore-errors).

IGNORE-ERRORS shouldn't be user at all, but if you must:

CG-USER(2): (ignore-errors (compile nil (lambda ()
(ignore-errors ((foo)))))
)
NIL
#<SIMPLE-ERROR @ #x20cc12b2>
From: Pascal Bourguignon
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <87k66i1yv1.fsf@thalassa.informatimago.com>
········@gmail.com writes:
>> I've tried this in ACL and MCL, and it doesn't work in either one.  Both
>> generate compiler errors for e.g. (my-function ignore-errors).
>
> IGNORE-ERRORS shouldn't be user at all, but if you must:
>
> CG-USER(2): (ignore-errors (compile nil (lambda ()
> (ignore-errors ((foo)))))
> )
> NIL
> #<SIMPLE-ERROR @ #x20cc12b2>


This fails in clisp-cvs :-( :

[28]> (ignore-errors (compile nil (lambda () (ignore-errors ((foo))))))

*** - SYSTEM::%EXPAND-FORM: (FOO) should be a lambda expression
The following restarts are available:
ABORT          :R1      ABORT
Break 1 [29]> 

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

Nobody can fix the economy.  Nobody can be trusted with their finger
on the button.  Nobody's perfect.  VOTE FOR NOBODY.
From: Ron Garret
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-30AA39.12215512072006@news.gha.chartermi.net>
In article <··············@thalassa.informatimago.com>,
 Pascal Bourguignon <···@informatimago.com> wrote:

> ········@gmail.com writes:
> >> I've tried this in ACL and MCL, and it doesn't work in either one.  Both
> >> generate compiler errors for e.g. (my-function ignore-errors).
> >
> > IGNORE-ERRORS shouldn't be user at all, but if you must:
> >
> > CG-USER(2): (ignore-errors (compile nil (lambda ()
> > (ignore-errors ((foo)))))
> > )
> > NIL
> > #<SIMPLE-ERROR @ #x20cc12b2>
> 
> 
> This fails in clisp-cvs :-( :
> 
> [28]> (ignore-errors (compile nil (lambda () (ignore-errors ((foo))))))
> 
> *** - SYSTEM::%EXPAND-FORM: (FOO) should be a lambda expression
> The following restarts are available:
> ABORT          :R1      ABORT
> Break 1 [29]>

MCL as well:

? (ignore-errors (compile nil (lambda ()
(ignore-errors ((foo))))))
> Error: While compiling an anonymous function :
>        #1=(FOO) is not a symbol or lambda expression in the form (#1#) .
> Type Command-. to abort.
See the Restarts... menu item for further choices.
1 >
From: ········@gmail.com
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152733840.465058.11500@35g2000cwc.googlegroups.com>
In case it wasn't obvious, the example I provided was ACL(7.0). The
BioBike/KnowOS system incrementally (and safely) compiles every form
entered into the web listener and uses exception handling to trap
compilation errors, reporting them back to the user. It would be
impossible to do this if ACL didn't report compiler errors through the
proper Lisp exception handling channels. Maybe you guys should stop
screwing around with toys and buy a modern, supported, Lisp
implementation.
From: Thomas F. Burdick
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <xcvsll569vo.fsf@conquest.OCF.Berkeley.EDU>
········@gmail.com writes:

> In case it wasn't obvious, the example I provided was ACL(7.0). The
> BioBike/KnowOS system incrementally (and safely) compiles every form
> entered into the web listener and uses exception handling to trap
> compilation errors, reporting them back to the user. It would be
> impossible to do this if ACL didn't report compiler errors through the
> proper Lisp exception handling channels. Maybe you guys should stop
> screwing around with toys and buy a modern, supported, Lisp
> implementation.

No, that's not the problem here.  This:

  (funcall (compile nil '(lambda () (ignore-errors ((foo))))))

and this:

  (ignore-errors (funcall (compile nil '(lambda () ((foo))))))

have different semantics wrt handling the errors produced by compiling
the ((foo)) bit.  I'm guessing the BioBike/KnowOS system does
something more akin to the latter.  The examples bandied about in this
thread are variations on the former.
From: ········@gmail.com
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152804425.112995.299620@m73g2000cwd.googlegroups.com>
> This:
>   (funcall (compile nil '(lambda () (ignore-errors ((foo))))))
> and this:
>   (ignore-errors (funcall (compile nil '(lambda () ((foo))))))
> have different semantics wrt handling the errors produced by compiling
> the ((foo)) bit.  I'm guessing the BioBike/KnowOS system does
> something more akin to the latter.  The examples bandied about in this
> thread are variations on the former.

Huh? Well, yeah, that how I solved Ron's first-level problem, but
that's not the second level problem: It seems like the compiler in SBCL
and MCL aren't throwing exceptions in a way that can be caught by
standard exception handling. Otherwise why can't those folks get my
version to work in their Lisps?
From: Ron Garret
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-E2FBA2.09202413072006@news.gha.chartermi.net>
In article <························@m73g2000cwd.googlegroups.com>,
 ········@gmail.com wrote:

> > This:
> >   (funcall (compile nil '(lambda () (ignore-errors ((foo))))))
> > and this:
> >   (ignore-errors (funcall (compile nil '(lambda () ((foo))))))
> > have different semantics wrt handling the errors produced by compiling
> > the ((foo)) bit.  I'm guessing the BioBike/KnowOS system does
> > something more akin to the latter.  The examples bandied about in this
> > thread are variations on the former.
> 
> Huh? Well, yeah, that how I solved Ron's first-level problem, but
> that's not the second level problem: It seems like the compiler in SBCL
> and MCL aren't throwing exceptions in a way that can be caught by
> standard exception handling. Otherwise why can't those folks get my
> version to work in their Lisps?

That's not the problem.  MCL does throw compiler exceptions in the 
standard way:

?  (ignore-errors (compile nil '(lambda () ((foo)))))
NIL
#<CCL::COMPILE-TIME-PROGRAM-ERROR #x24B9F8E>
? 

However:

?  (ignore-errors (compile nil (lambda () ((foo)))))
> Error: While compiling an anonymous function :
>        #1=(FOO) is not a symbol or lambda expression in the form (#1#) .
> Type Command-. to abort.
See the Restarts� menu item for further choices.
1 > 

This is because MCL implements EVAL as (essentially):

(defun eval (form) (funcall (compile nil `(lambda () ,form))))

So when you don't quote the lambda expression it gets compiled outside 
the scope of the ignore-errors.

But when you do quote the lambda expression then you lose lexical 
scoping.

Either way I seem to be screwed.

rg
From: ········@gmail.com
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152808833.651775.78660@s13g2000cwa.googlegroups.com>
> This is because MCL implements EVAL as (essentially):
>
> (defun eval (form) (funcall (compile nil `(lambda () ,form))))
>
> So when you don't quote the lambda expression it gets compiled outside
> the scope of the ignore-errors.
>
> But when you do quote the lambda expression then you lose lexical
> scoping.

So how does ACL implement this so that it works (and does preserve
scoping)?
From: Ron Garret
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-5204A1.10211213072006@news.gha.chartermi.net>
In article <·······················@s13g2000cwa.googlegroups.com>,
 ········@gmail.com wrote:

> > This is because MCL implements EVAL as (essentially):
> >
> > (defun eval (form) (funcall (compile nil `(lambda () ,form))))
> >
> > So when you don't quote the lambda expression it gets compiled outside
> > the scope of the ignore-errors.
> >
> > But when you do quote the lambda expression then you lose lexical
> > scoping.
> 
> So how does ACL implement this so that it works (and does preserve
> scoping)?

ACL has a real interpreter.

rg
From: Juho Snellman
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <slrnebdgih.mrk.jsnell@sbz-30.cs.Helsinki.FI>
········@gmail.com <········@gmail.com> wrote:
>> This is because MCL implements EVAL as (essentially):
>>
>> (defun eval (form) (funcall (compile nil `(lambda () ,form))))
>>
>> So when you don't quote the lambda expression it gets compiled outside
>> the scope of the ignore-errors.
>>
>> But when you do quote the lambda expression then you lose lexical
>> scoping.
> 
> So how does ACL implement this so that it works (and does preserve
> scoping)?

It doesn't. What Ron needed was something like this:

    (defun foo () (or (ignore-errors #'(bar)) (print 'bar)))    

Your suggestion was essentially that it be written as:

    (defun foo ()
      (or (ignore-errors 
            (funcall (compile nil (lambda ()
	                             (ignore-errors #'(bar))))))
	  (print 'bar)))
	  
So, let's try that on ACL:

    Trying 206.169.106.7...
    Connected to prompt.franz.com.
    Escape character is '^]'.
    International Allegro CL Trial Edition
    7.0 [Linux (x86)] (May 12, 2006 9:20)
    Copyright (C) 1985-2004, Franz Inc., Oakland, CA, USA.  All Rights Reserved.
    
    This development copy of Allegro CL is licensed to:
       QA
    
    ;; Optimization settings: safety 1, space 1, speed 1, debug 2.
    ;; For a complete description of all compiler switches given the
    ;; current optimization settings evaluate (EXPLAIN-COMPILER-SETTINGS).
    CL-USER(1): (defun foo ()
               (or (ignore-errors 
                     (funcall (compile nil (lambda ()
                                             (ignore-errors #'(bar))))))
                   (print 'bar)))
    FOO
    CL-USER(2): (foo)
    
    BAR 
    BAR

Yay! Except...
    
    CL-USER(3): (compile 'foo)
    ; While compiling (:INTERNAL FOO 0):
    Error: (BAR) is not a valid function spec
      [condition type: TYPE-ERROR]
    
    Restart actions (select using :continue):
     0: Return to Top Level (an "abort" restart).
     1: Abort entirely from this (lisp) process.
     
Oops. Now, we could try sprinkling around even more IGNORE-ERRORS...
     
    [1] CL-USER(4): (ignore-errors (compile 'foo))
    ; While compiling (:INTERNAL FOO 0):
    NIL
    #<TYPE-ERROR @ #x71636d02>

... but obviously that doesn't work.    

    [1] CL-USER(5): (compiled-function-p 'foo)
    NIL

-- 
Juho Snellman
From: Juho Snellman
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <slrnebdcjf.mrk.jsnell@sbz-30.cs.Helsinki.FI>
········@gmail.com <········@gmail.com> wrote:
> Huh? Well, yeah, that how I solved Ron's first-level problem, but
> that's not the second level problem: It seems like the compiler in SBCL
> and MCL aren't throwing exceptions in a way that can be caught by
> standard exception handling. Otherwise why can't those folks get my
> version to work in their Lisps?

I don't know why you claim that your version doesn't work in SBCL. It
does. The way compilation erros are handled in CMUCL and SBCL has
already been described in detail twice in this thread, so I won't do
it a third time.

-- 
Juho Snellman
From: Joe Marshall
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152725514.648446.224840@35g2000cwc.googlegroups.com>
Ron Garret wrote:
> What should (ignore-errors ((foo))) do?

I've been thinking about this.  There is sort of a continuum of bad
code that you could imagine trying to run:

(ignore-errors (lambda))

(ignore-errors (3 'foo))

(ignore-errors (car "foobar"))

(ignore-errors (aref x (+ array-dimension-limit 1)))

(eval '(ignore-errors ((foo))))

(ignore-errors (eval '((foo))))

I like having the compiler tell me when it finds bogus code, but I
*really* like the idea that EVAL is essentially transparent (modulo
scoping).  In other words, for any form <foo>, (eval (quote <foo>))
should have the same value.  Obviously this can't be achieved
completely.

Given that, I guess I'd like *all* the above forms to return NIL.  I'll
bet there are people that would disagree and draw the line elsewhere.

> If you think it should return NIL, what should (compile nil (lambda ()
> (ignore-errors ((foo))))) do?

It seems to me that it *ought* to compile to a function that returns
NIL.

> And in case you're wondering why I'm asking, I want to define a macro
> that works just like FUNCTION except that if FUNCTION would return an
> error it does some special processing

Another reason I don't want the compiler to barf on bad code is because
this puts a burden on macro writers to ensure that macro results are
syntactically correct even in unusual situations.  For instance:
(defmacro foo (x)
  `(if (consp ,x)
       (car ,x)
       (aref ,x 0)))

(foo "bar") =>
   (if (consp "bar")
       (car "bar")
       (aref "bar" 0))

The code in the if consequent is obviously bogus, but just as obviously
dead code.  It would be bad if the compiler refused to compile this.  A
more complex macro could easily expand into code that is syntactically
bogus, yet semantically reasonable.  I'd like my compiler to tell me
that something fishy is going on, but I need it to trust that I know
what I am doing.
From: anon
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <DPOdnSpGKZCaiyjZnZ2dnUVZ_tydnZ2d@comcast.com>
Ron Garret <·········@flownet.com> wrote:
RG> 
RG> What should (ignore-errors ((foo))) do?
RG> 
RG> If you think it should return NIL, what should (compile nil (lambda () 
RG> (ignore-errors ((foo))))) do?
RG> 
RG> And in case you're wondering why I'm asking, I want to define a macro 
RG> that works just like FUNCTION except that if FUNCTION would return an 
RG> error it does some special processing, i.e. something like:
RG> 
RG> (defmacro my-function (thing)
RG>   `(or (ignore-errors (function, thing)) (special-processing thing))))
RG> 
RG> I've tried this in ACL and MCL, and it doesn't work in either one.  Both 
RG> generate compiler errors for e.g. (my-function ignore-errors).
RG> 
RG> rg

I have something like this to capture all errors
to a log file.  would that work?

(defmacro ignore-all-errors (&rest body)
  `(handler-case
    ,@body
    (condition (var) (write-log var) nil)))
From: Ron Garret
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-C18541.12225412072006@news.gha.chartermi.net>
In article <································@comcast.com>,
 ·············@comcast.net (anon) wrote:

> Ron Garret <·········@flownet.com> wrote:
> RG> 
> RG> What should (ignore-errors ((foo))) do?
> RG> 
> RG> If you think it should return NIL, what should (compile nil (lambda () 
> RG> (ignore-errors ((foo))))) do?
> RG> 
> RG> And in case you're wondering why I'm asking, I want to define a macro 
> RG> that works just like FUNCTION except that if FUNCTION would return an 
> RG> error it does some special processing, i.e. something like:
> RG> 
> RG> (defmacro my-function (thing)
> RG>   `(or (ignore-errors (function, thing)) (special-processing thing))))
> RG> 
> RG> I've tried this in ACL and MCL, and it doesn't work in either one.  Both 
> RG> generate compiler errors for e.g. (my-function ignore-errors).
> RG> 
> RG> rg
> 
> I have something like this to capture all errors
> to a log file.  would that work?
> 
> (defmacro ignore-all-errors (&rest body)
>   `(handler-case
>     ,@body
>     (condition (var) (write-log var) nil)))

Nope:

? (ignore-all-errors ((foo)))
> Error: While compiling an anonymous function :
>        #1=(FOO) is not a symbol or lambda expression in the form (#1#) .
> Type Command-. to abort.
See the Restarts� menu item for further choices.
1 > 
Aborted
?
From: Pascal Costanza
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hnibcFeppjU1@individual.net>
Ron Garret wrote:
> What should (ignore-errors ((foo))) do?
> 
> If you think it should return NIL, what should (compile nil (lambda () 
> (ignore-errors ((foo))))) do?
> 
> And in case you're wondering why I'm asking, I want to define a macro 
> that works just like FUNCTION except that if FUNCTION would return an 
> error it does some special processing, i.e. something like:
> 
> (defmacro my-function (thing)
>   `(or (ignore-errors (function, thing)) (special-processing thing))))
> 
> I've tried this in ACL and MCL, and it doesn't work in either one.  Both 
> generate compiler errors for e.g. (my-function ignore-errors).

What's wrong with parsing thing?

(defmacro my-function (thing)
   (cond ((functionp thing) thing)
         ((symbolp thing) `(function ,thing))
         ((consp thing)
          (if (and (eq (car thing) 'lambda)
                   (length (cadr thing))
                   (length (cddr thing)))
            `(function ,thing)
            (special-processing thing)))
         (t (error "Unexpected thing ~S." thing))))


Pascal

-- 
3rd European Lisp Workshop
July 3 - Nantes, France - co-located with ECOOP 2006
http://lisp-ecoop06.bknr.net/
From: Ron Garret
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-E94DC8.12380613072006@news.gha.chartermi.net>
In article <·············@individual.net>,
 Pascal Costanza <··@p-cos.net> wrote:

> Ron Garret wrote:
> > What should (ignore-errors ((foo))) do?
> > 
> > If you think it should return NIL, what should (compile nil (lambda () 
> > (ignore-errors ((foo))))) do?
> > 
> > And in case you're wondering why I'm asking, I want to define a macro 
> > that works just like FUNCTION except that if FUNCTION would return an 
> > error it does some special processing, i.e. something like:
> > 
> > (defmacro my-function (thing)
> >   `(or (ignore-errors (function, thing)) (special-processing thing))))
> > 
> > I've tried this in ACL and MCL, and it doesn't work in either one.  Both 
> > generate compiler errors for e.g. (my-function ignore-errors).
> 
> What's wrong with parsing thing?
> 
> (defmacro my-function (thing)
>    (cond ((functionp thing) thing)
>          ((symbolp thing) `(function ,thing))
>          ((consp thing)
>           (if (and (eq (car thing) 'lambda)
>                    (length (cadr thing))
>                    (length (cddr thing)))
>             `(function ,thing)
>             (special-processing thing)))
>          (t (error "Unexpected thing ~S." thing))))

Doesn't work:

? (my-function blatz)
> Error: Undefined function: BLATZ
> While executing: CCL::%FUNCTION
> Type Command-. to abort.
See the Restarts� menu item for further choices.
1 > 

The tricky part is intercepting the case where you pass a symbol that is 
not fbound.  The reason it's tricky is that as far as I know there's no 
portable way to tell if a symbol is locally fbound (with FLET or LABELS).

rg
From: Pascal Costanza
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hnr1oFfv4sU1@individual.net>
Ron Garret wrote:
> In article <·············@individual.net>,
>  Pascal Costanza <··@p-cos.net> wrote:
> 
>> Ron Garret wrote:
>>> What should (ignore-errors ((foo))) do?
>>>
>>> If you think it should return NIL, what should (compile nil (lambda () 
>>> (ignore-errors ((foo))))) do?
>>>
>>> And in case you're wondering why I'm asking, I want to define a macro 
>>> that works just like FUNCTION except that if FUNCTION would return an 
>>> error it does some special processing, i.e. something like:
>>>
>>> (defmacro my-function (thing)
>>>   `(or (ignore-errors (function, thing)) (special-processing thing))))
>>>
>>> I've tried this in ACL and MCL, and it doesn't work in either one.  Both 
>>> generate compiler errors for e.g. (my-function ignore-errors).
>> What's wrong with parsing thing?
>>
>> (defmacro my-function (thing)
>>    (cond ((functionp thing) thing)
>>          ((symbolp thing) `(function ,thing))
>>          ((consp thing)
>>           (if (and (eq (car thing) 'lambda)
>>                    (length (cadr thing))
>>                    (length (cddr thing)))
>>             `(function ,thing)
>>             (special-processing thing)))
>>          (t (error "Unexpected thing ~S." thing))))
> 
> Doesn't work:
> 
> ? (my-function blatz)
>> Error: Undefined function: BLATZ
>> While executing: CCL::%FUNCTION
>> Type Command-. to abort.
> See the Restarts� menu item for further choices.
> 1 > 
> 
> The tricky part is intercepting the case where you pass a symbol that is 
> not fbound.  The reason it's tricky is that as far as I know there's no 
> portable way to tell if a symbol is locally fbound (with FLET or LABELS).

Yes, there is. It works roughly like this:

(shadow 'flet)

(define-symbol-macro %local-functions% ())

(defmacro flet (bindings &body body &environment env)
   (let ((outer-functions (macroexpand '%local-functions% env)))
     `(symbol-macrolet ((%local-functions%
                         ,(append
                            (mapcar #'car bindings)
                            outer-fuctions)))
        (cl:flet ,bindings ,@body))))

labels is left as an exercise. You should also shadow macrolet.

If you do this, you can use (macroexpand '%local-functions% env) to test 
for the presence of some local function inside macro definitions.

This particular code snippet is not tested, but I am using something 
similar in some of my own code, so I can tell you that this idiom works 
very well in principle.

You may want to add ignorable declarations for the new bindings for 
%local-functions%. (However, some CL implementations don't seem to like 
such declarations for symbol macros.) It's also important that the 
symbol-macrolet comes before the cl:flet, so that local declarations are 
processed correctly.


Pascal

-- 
3rd European Lisp Workshop
July 3 - Nantes, France - co-located with ECOOP 2006
http://lisp-ecoop06.bknr.net/
From: Ron Garret
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-4AC385.17094313072006@news.gha.chartermi.net>
In article <·············@individual.net>,
 Pascal Costanza <··@p-cos.net> wrote:

> Ron Garret wrote:
> > In article <·············@individual.net>,
> >  Pascal Costanza <··@p-cos.net> wrote:
> > 
> >> Ron Garret wrote:
> >>> What should (ignore-errors ((foo))) do?
> >>>
> >>> If you think it should return NIL, what should (compile nil (lambda () 
> >>> (ignore-errors ((foo))))) do?
> >>>
> >>> And in case you're wondering why I'm asking, I want to define a macro 
> >>> that works just like FUNCTION except that if FUNCTION would return an 
> >>> error it does some special processing, i.e. something like:
> >>>
> >>> (defmacro my-function (thing)
> >>>   `(or (ignore-errors (function, thing)) (special-processing thing))))
> >>>
> >>> I've tried this in ACL and MCL, and it doesn't work in either one.  Both 
> >>> generate compiler errors for e.g. (my-function ignore-errors).
> >> What's wrong with parsing thing?
> >>
> >> (defmacro my-function (thing)
> >>    (cond ((functionp thing) thing)
> >>          ((symbolp thing) `(function ,thing))
> >>          ((consp thing)
> >>           (if (and (eq (car thing) 'lambda)
> >>                    (length (cadr thing))
> >>                    (length (cddr thing)))
> >>             `(function ,thing)
> >>             (special-processing thing)))
> >>          (t (error "Unexpected thing ~S." thing))))
> > 
> > Doesn't work:
> > 
> > ? (my-function blatz)
> >> Error: Undefined function: BLATZ
> >> While executing: CCL::%FUNCTION
> >> Type Command-. to abort.
> > See the RestartsS� menu item for further choices.
> > 1 > 
> > 
> > The tricky part is intercepting the case where you pass a symbol that is 
> > not fbound.  The reason it's tricky is that as far as I know there's no 
> > portable way to tell if a symbol is locally fbound (with FLET or LABELS).
> 
> Yes, there is. It works roughly like this:
> 
> (shadow 'flet)

You of all people should realize why this doesn't work.  Shadowing FLET 
only works for code that lives in the package where FLET is shadowed.  
So, for example, if I use a third-party macro that uses FLET or LABELS 
in its expansion then I lose.

rg
From: Pascal Costanza
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hp3obFkshhU1@individual.net>
Ron Garret wrote:
> In article <·············@individual.net>,
>  Pascal Costanza <··@p-cos.net> wrote:
> 
>> Ron Garret wrote:
>>> In article <·············@individual.net>,
>>>  Pascal Costanza <··@p-cos.net> wrote:
>>>
>>>> Ron Garret wrote:
>>>>> What should (ignore-errors ((foo))) do?
>>>>>
>>>>> If you think it should return NIL, what should (compile nil (lambda () 
>>>>> (ignore-errors ((foo))))) do?
>>>>>
>>>>> And in case you're wondering why I'm asking, I want to define a macro 
>>>>> that works just like FUNCTION except that if FUNCTION would return an 
>>>>> error it does some special processing, i.e. something like:
>>>>>
>>>>> (defmacro my-function (thing)
>>>>>   `(or (ignore-errors (function, thing)) (special-processing thing))))
>>>>>
>>>>> I've tried this in ACL and MCL, and it doesn't work in either one.  Both 
>>>>> generate compiler errors for e.g. (my-function ignore-errors).
>>>> What's wrong with parsing thing?
>>>>
>>>> (defmacro my-function (thing)
>>>>    (cond ((functionp thing) thing)
>>>>          ((symbolp thing) `(function ,thing))
>>>>          ((consp thing)
>>>>           (if (and (eq (car thing) 'lambda)
>>>>                    (length (cadr thing))
>>>>                    (length (cddr thing)))
>>>>             `(function ,thing)
>>>>             (special-processing thing)))
>>>>          (t (error "Unexpected thing ~S." thing))))
>>> Doesn't work:
>>>
>>> ? (my-function blatz)
>>>> Error: Undefined function: BLATZ
>>>> While executing: CCL::%FUNCTION
>>>> Type Command-. to abort.
>>> See the RestartsS� menu item for further choices.
>>> 1 > 
>>>
>>> The tricky part is intercepting the case where you pass a symbol that is 
>>> not fbound.  The reason it's tricky is that as far as I know there's no 
>>> portable way to tell if a symbol is locally fbound (with FLET or LABELS).
>> Yes, there is. It works roughly like this:
>>
>> (shadow 'flet)
> 
> You of all people should realize why this doesn't work.  Shadowing FLET 
> only works for code that lives in the package where FLET is shadowed.  
> So, for example, if I use a third-party macro that uses FLET or LABELS 
> in its expansion then I lose.

It may not be a total solution, but it certainly works well enough to be 
workable. It's also not unlike other opportunities for language 
extensions in Common Lisp which only work reliably when users restrict 
themselves to the language that includes those extensions. Indeed, it is 
a known issue that different language extensions are in general not 
compatible. ("In general" here means not only in Common Lisp, but in all 
programming languages, no matter how you attempt to extend a language.)

My advice would be not to worry too much about totality, but worry more 
about pragmatics.


Pascal

-- 
3rd European Lisp Workshop
July 3 - Nantes, France - co-located with ECOOP 2006
http://lisp-ecoop06.bknr.net/
From: Ron Garret
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-F96EB6.09484314072006@news.gha.chartermi.net>
In article <·············@individual.net>,
 Pascal Costanza <··@p-cos.net> wrote:

> My advice would be not to worry too much about totality, but worry more 
> about pragmatics.

I'm working on a module system, the pragmatic utility of which would be 
severely limited it breaks when using code in other packages.

rg
From: Pascal Costanza
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hq169Foui5U1@individual.net>
Ron Garret wrote:
> In article <·············@individual.net>,
>  Pascal Costanza <··@p-cos.net> wrote:
> 
>> My advice would be not to worry too much about totality, but worry more 
>> about pragmatics.
> 
> I'm working on a module system, the pragmatic utility of which would be 
> severely limited it breaks when using code in other packages.

...in that case I think your biggest problem is not whether 
ignore-errors handles certain errors or not. See 
http://repository.readscheme.org/ftp/papers/sw2002/queinnec-modules.pdf


Pascal

-- 
My website: http://p-cos.net
Closer to MOP & ContextL:
http://common-lisp.net/project/closer/
From: Ron Garret
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-BC16F2.11083714072006@news.gha.chartermi.net>
In article <·············@individual.net>,
 Pascal Costanza <··@p-cos.net> wrote:

> Ron Garret wrote:
> > In article <·············@individual.net>,
> >  Pascal Costanza <··@p-cos.net> wrote:
> > 
> >> My advice would be not to worry too much about totality, but worry more 
> >> about pragmatics.
> > 
> > I'm working on a module system, the pragmatic utility of which would be 
> > severely limited it breaks when using code in other packages.
> 
> ...in that case I think your biggest problem is not whether 
> ignore-errors handles certain errors or not.

Unfortunately, just because that may not be my biggest problem doesn't 
mean I can ignore it.

> See 
> http://repository.readscheme.org/ftp/papers/sw2002/queinnec-modules.pdf

Happily, I am not trying to write a module system for Scheme.

rg
From: Pascal Costanza
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hq7dbFqgj6U2@individual.net>
Ron Garret wrote:
> In article <·············@individual.net>,
>  Pascal Costanza <··@p-cos.net> wrote:
> 
>> Ron Garret wrote:
>>> In article <·············@individual.net>,
>>>  Pascal Costanza <··@p-cos.net> wrote:
>>>
>>>> My advice would be not to worry too much about totality, but worry more 
>>>> about pragmatics.
>>> I'm working on a module system, the pragmatic utility of which would be 
>>> severely limited it breaks when using code in other packages.
>> ...in that case I think your biggest problem is not whether 
>> ignore-errors handles certain errors or not.
> 
> Unfortunately, just because that may not be my biggest problem doesn't 
> mean I can ignore it.
> 
>> See 
>> http://repository.readscheme.org/ftp/papers/sw2002/queinnec-modules.pdf
> 
> Happily, I am not trying to write a module system for Scheme.

...but one for a language that has macros.


Pascal

-- 
My website: http://p-cos.net
Closer to MOP & ContextL:
http://common-lisp.net/project/closer/
From: Ron Garret
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <rNOSPAMon-8F3851.15032714072006@news.gha.chartermi.net>
In article <·············@individual.net>,
 Pascal Costanza <··@p-cos.net> wrote:

> Ron Garret wrote:
> > In article <·············@individual.net>,
> >  Pascal Costanza <··@p-cos.net> wrote:
> > 
> >> Ron Garret wrote:
> >>> In article <·············@individual.net>,
> >>>  Pascal Costanza <··@p-cos.net> wrote:
> >>>
> >>>> My advice would be not to worry too much about totality, but worry more 
> >>>> about pragmatics.
> >>> I'm working on a module system, the pragmatic utility of which would be 
> >>> severely limited it breaks when using code in other packages.
> >> ...in that case I think your biggest problem is not whether 
> >> ignore-errors handles certain errors or not.
> > 
> > Unfortunately, just because that may not be my biggest problem doesn't 
> > mean I can ignore it.
> > 
> >> See 
> >> http://repository.readscheme.org/ftp/papers/sw2002/queinnec-modules.pdf
> > 
> > Happily, I am not trying to write a module system for Scheme.
> 
> ...but one for a language that has macros.

Of course.  That's why we're all here, isn't it?

rg
From: Pascal Costanza
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hrd34Fr0e7U1@individual.net>
Ron Garret wrote:
> In article <·············@individual.net>,
>  Pascal Costanza <··@p-cos.net> wrote:
> 
>> Ron Garret wrote:
>>> In article <·············@individual.net>,
>>>  Pascal Costanza <··@p-cos.net> wrote:
>>>
>>>> Ron Garret wrote:
>>>>> In article <·············@individual.net>,
>>>>>  Pascal Costanza <··@p-cos.net> wrote:
>>>>>
>>>>>> My advice would be not to worry too much about totality, but worry more 
>>>>>> about pragmatics.
>>>>> I'm working on a module system, the pragmatic utility of which would be 
>>>>> severely limited it breaks when using code in other packages.
>>>> ...in that case I think your biggest problem is not whether 
>>>> ignore-errors handles certain errors or not.
>>> Unfortunately, just because that may not be my biggest problem doesn't 
>>> mean I can ignore it.
>>>
>>>> See 
>>>> http://repository.readscheme.org/ftp/papers/sw2002/queinnec-modules.pdf
>>> Happily, I am not trying to write a module system for Scheme.
>> ...but one for a language that has macros.
> 
> Of course.  That's why we're all here, isn't it?

Isn't it amazing?

Since Scheme is a language with macros as well, some of the issues 
Christian Queinnec mentions in that paper are relevant for Common Lisp 
as well.


Pascal

-- 
My website: http://p-cos.net
Closer to MOP & ContextL:
http://common-lisp.net/project/closer/
From: Marcin 'Qrczak' Kowalczyk
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <87sll5l1z1.fsf@qrnik.zagroda>
Ron Garret <·········@flownet.com> writes:

> What should (ignore-errors ((foo))) do?

It should be an error. IGNORE-ERRORS catches evaluation (runtime)
errors, not compilation errors.

Perhaps Lisp doesn't separate these kinds of errors as well as it
should.

-- 
   __("<         Marcin Kowalczyk
   \__/       ······@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/
From: Nathan Baum
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152824026.776903.135150@h48g2000cwc.googlegroups.com>
Marcin 'Qrczak' Kowalczyk wrote:
> Ron Garret <·········@flownet.com> writes:
>
> > What should (ignore-errors ((foo))) do?
>
> It should be an error. IGNORE-ERRORS catches evaluation (runtime)
> errors, not compilation errors.

I'm pretty sure the specification places no such limitations upon
IGNORE-ERRORS. Additionally, I don't think the specification says
anything about what should happen when "((foo))" is evaluated, except
that it shouldn't be. I guess the implementation can do what it likes.

> Perhaps Lisp doesn't separate these kinds of errors as well as it
> should.

This smacks of a compile-time vs. runtime mentality which doesn't mesh
with my understanding of Lisp. "(ignore-errors ((foo)))" needn't be
compiled to be evaluated, and I don't think minimal compilation says
anything about dealing with syntax errors, so even if it _was_
compiled, I don't think "((foo))" is necessarily a compilation error,
anyway.

> --
>    __("<         Marcin Kowalczyk
>    \__/       ······@knm.org.pl
>     ^^     http://qrnik.knm.org.pl/~qrczak/
From: Marcin 'Qrczak' Kowalczyk
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <87mzbdgmld.fsf@qrnik.zagroda>
"Nathan Baum" <···········@btinternet.com> writes:

>> It should be an error. IGNORE-ERRORS catches evaluation (runtime)
>> errors, not compilation errors.
>
> I'm pretty sure the specification places no such limitations upon
> IGNORE-ERRORS.

The specification is either unclear or makes this an error. I's
probably unspecified, but I answered how I think it *should* be done.

If it was unambiguously not an error, it would mean that ((foo))
is a valid form which signals a condition when executed, rather
than an invalid form. It would mean that
   (when nil ((foo)))
is not an error and Lisps are required to execute it successfully.
It doesn't seem to be a good idea for me. What about other
syntactically invalid forms, e.g.
   (when nil (let x y z))
? Catching such errors without executing these subforms is easy,
it doesn't interfere with expressing sensible programs. Signalling
such error as early as possible is advantageous for the user.

> This smacks of a compile-time vs. runtime mentality which doesn't
> mesh with my understanding of Lisp.

Well, this is one of things I hate in Lisp: too many aspects are
unspecified, in particular those regarding phases of execution
(what is visible in which environment, when errors are signalled).

These ambiguities might be more convenient for legacy implementations,
but they serve no purpose for users. They just hinder portability.


Pascal Costanza <··@p-cos.net> writes:

>> Perhaps Lisp doesn't separate these kinds of errors as well as it
>> should.
>
> Based on what criterion should Lisp do this?

When a given kind of error is always discoverable without running
the code, then it's a static error (compile error), otherwise it's
a dynamic error (runtime error).

For example (/ 1 0) or (+ "a" "b") are dynamic errors. It should be
valid to put such forms in the code as long as they are not executed.
An implementation which rejects them statically (e.g. when constant
folding) is faulty, although warning about them is fine. A macro
should be allowed to leave them as dead code after some variable
substitution.

Similarly calling a function with a wrong number of arguments is a
dynamic error. And referring to a non-existent lexical variable is a
static error. Easy.

Why to leave the semantics ambiguous in this respect?

-- 
   __("<         Marcin Kowalczyk
   \__/       ······@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/
From: Nathan Baum
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <1152833705.222955.116930@75g2000cwc.googlegroups.com>
Marcin 'Qrczak' Kowalczyk wrote:
> "Nathan Baum" <···········@btinternet.com> writes:
>
> >> It should be an error. IGNORE-ERRORS catches evaluation (runtime)
> >> errors, not compilation errors.
> >
> > I'm pretty sure the specification places no such limitations upon
> > IGNORE-ERRORS.
>
> The specification is either unclear or makes this an error. I's
> probably unspecified, but I answered how I think it *should* be done.
>
> If it was unambiguously not an error, it would mean that ((foo))
> is a valid form which signals a condition when executed, rather
> than an invalid form. It would mean that
>    (when nil ((foo)))
> is not an error and Lisps are required to execute it successfully.

I think that's fine.

> It doesn't seem to be a good idea for me. What about other
> syntactically invalid forms, e.g.
>    (when nil (let x y z))
> ? Catching such errors without executing these subforms is easy,
> it doesn't interfere with expressing sensible programs. Signalling
> such error as early as possible is advantageous for the user.

You mean for the _developer_, surely.

I think the real question is whether or not the developer is to be
_prohibited_ from writing invalid forms which are never executed, or
merely _sternly warned_ about it. The user can be protected by not
allowing developers to ship products with certain "latent" errors in
them. (when nil (let x y z)) can be prohibited in production code, but
I see no particular _need_ to prohibit it in unfinished code.

> > This smacks of a compile-time vs. runtime mentality which doesn't
> > mesh with my understanding of Lisp.
>
> Well, this is one of things I hate in Lisp: too many aspects are
> unspecified, in particular those regarding phases of execution
> (what is visible in which environment, when errors are signalled).

I don't think Lisp _has_ phases of execution. Lisp isn't like C.
Compile-time and run-time can be mixed up. New source can be loaded and
compiled on a running system. This is on purpose.

> These ambiguities might be more convenient for legacy implementations,
> but they serve no purpose for users. They just hinder portability.

This is true, but I don't think the solution is a clear distinction
between "compile time" and "run time".

My prefered solution would be to permit, where possible, a compiled
program to behave like an interpreted program. This would entail not
permitting (compile) et al to signal conditions upon failure. On the
other hand, the programmer should be allowed to request that
compilation errors not be muffled by (compile). Combined with a
compiler-error condition type which include the filename, line number
and whathaveyou, such a feature would give a portable interface to
compilation which editors would probably find useful.

I just don't think that a "one-size-fits-all" solution is good here.
Particularly one which potentially breaks a lot of existing code.

> When a given kind of error is always discoverable without running
> the code, then it's a static error (compile error), otherwise it's
> a dynamic error (runtime error).
>
> For example (/ 1 0) or (+ "a" "b") are dynamic errors. It should be
> valid to put such forms in the code as long as they are not executed.

But the errors in (/ 1 0) and (+ "a" "b") seem to be perfectly
discoverable without running the code. Of course, it's possible that /
and + might be redefined. The standard leaves the consquences of
redefining / and + undefined, which means an implementation might
permit it.

> Similarly calling a function with a wrong number of arguments is a
> dynamic error. And referring to a non-existent lexical variable is a
> static error. Easy.

Referring to a non-existent lexical variable within a function
definition _isn't_ a static error: you can't prove it wrong at compile
time, unless you consider the entire system (which may not even be
available at compile time).

  ;; foo.lisp
  (defun foo ()
    bar)

  ;; bar.lisp
  (defvar bar 42)

  ;; main.lisp
  (load (compile-file "foo.lisp"))
  (load (compile-file "bar.lisp"))
  (print (foo))

The compilation of foo.lisp may merit a warning (which it gets in
SBCL), but I don't think it should be an _error_, since the code as a
whole obviously works.

>
> Why to leave the semantics ambiguous in this respect?
>
> --
>    __("<         Marcin Kowalczyk
>    \__/       ······@knm.org.pl
>     ^^     http://qrnik.knm.org.pl/~qrczak/
From: Pascal Costanza
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4ho3gsFh8lrU1@individual.net>
Marcin 'Qrczak' Kowalczyk wrote:
> 
>>> It should be an error. IGNORE-ERRORS catches evaluation (runtime)
>>> errors, not compilation errors.
> 
>>> Perhaps Lisp doesn't separate these kinds of errors as well as it
>>> should.
>> Based on what criterion should Lisp do this?
> 
> When a given kind of error is always discoverable without running
> the code, then it's a static error (compile error), otherwise it's
> a dynamic error (runtime error).
> 
> For example (/ 1 0) or (+ "a" "b") are dynamic errors. It should be
> valid to put such forms in the code as long as they are not executed.
> An implementation which rejects them statically (e.g. when constant
> folding) is faulty, although warning about them is fine. A macro
> should be allowed to leave them as dead code after some variable
> substitution.
> 
> Similarly calling a function with a wrong number of arguments is a
> dynamic error. And referring to a non-existent lexical variable is a
> static error. Easy.
> 
> Why to leave the semantics ambiguous in this respect?

Maybe I misunderstood your previous posting, but it seems to state that 
(ignore-errors ((foo))) should be an error at compile time. If this is 
not what you said, I am sorry that I have misunderstood you.

Nevertheless, I am not so sure whether your criterion is really that 
clear cut. Consider this:

(defun foo () (/ 1 0))

This function will always fail at runtime, and this can already be 
detected at compile time. (Common Lisp disallows changing the definition 
of /.)

Then consider this:

(defun bar ()
   (if nil x 42))

Let's assume that x is not globally defined. So we have a free variable, 
but the code would always succeed anyway. This can even be detected 
statically. So why should this yield an error at all?

There is no "natural" reason why some of these things are compile-time 
errors and others are not. These are "just" (hopefully specified) 
conventions.


Pascal

-- 
3rd European Lisp Workshop
July 3 - Nantes, France - co-located with ECOOP 2006
http://lisp-ecoop06.bknr.net/
From: Leonid Slobodov
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <44b7580d$0$26261$9b4e6d93@newsread2.arcor-online.net>
Pascal Costanza wrote:

> Maybe I misunderstood your previous posting, but it seems to state that
> (ignore-errors ((foo))) should be an error at compile time. If this is
> not what you said, I am sorry that I have misunderstood you.
> 
> Nevertheless, I am not so sure whether your criterion is really that
> clear cut. Consider this:
> 
> (defun foo () (/ 1 0))
> 
> This function will always fail at runtime, and this can already be
> detected at compile time. (Common Lisp disallows changing the definition
> of /.)
> 
> Then consider this:
> 
> (defun bar ()
>    (if nil x 42))
> 
> Let's assume that x is not globally defined. So we have a free variable,
> but the code would always succeed anyway. This can even be detected
> statically. So why should this yield an error at all?
> 
> There is no "natural" reason why some of these things are compile-time
> errors and others are not. These are "just" (hopefully specified)
> conventions.
> 
> 
> Pascal
> 

All of that is fine, but I always thought that (ignore-errors foo)
does an equivalent of (handler-bind foo (error (c) (values nil c)).
This clearly has runtime semantics.
It would probably cause serious breakage if this form would suddenly
catch compile-time errors.

Another thing is (ignore-errors (compile nil '(lambda () ((foo))))).
((foo))'s compile-time is the runtime of ignore-errors, thus the error
is caught. 
From: Pascal Costanza
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hp3v9FkshhU2@individual.net>
Leonid Slobodov wrote:
> Pascal Costanza wrote:
> 
>> Maybe I misunderstood your previous posting, but it seems to state that
>> (ignore-errors ((foo))) should be an error at compile time. If this is
>> not what you said, I am sorry that I have misunderstood you.
>>
>> Nevertheless, I am not so sure whether your criterion is really that
>> clear cut. Consider this:
>>
>> (defun foo () (/ 1 0))
>>
>> This function will always fail at runtime, and this can already be
>> detected at compile time. (Common Lisp disallows changing the definition
>> of /.)
>>
>> Then consider this:
>>
>> (defun bar ()
>>    (if nil x 42))
>>
>> Let's assume that x is not globally defined. So we have a free variable,
>> but the code would always succeed anyway. This can even be detected
>> statically. So why should this yield an error at all?
>>
>> There is no "natural" reason why some of these things are compile-time
>> errors and others are not. These are "just" (hopefully specified)
>> conventions.
>>
>>
>> Pascal
>>
> 
> All of that is fine, but I always thought that (ignore-errors foo)
> does an equivalent of (handler-bind foo (error (c) (values nil c)).
> This clearly has runtime semantics.
> It would probably cause serious breakage if this form would suddenly
> catch compile-time errors.


Sure, but ((foo)) is not specified to be a compile-time error.



Pascal

-- 
3rd European Lisp Workshop
July 3 - Nantes, France - co-located with ECOOP 2006
http://lisp-ecoop06.bknr.net/
From: Ron Garret
Subject: What should (ignore-errors (function foo)) do (was: Re: What should (ignore-errors ((foo))) do?)
Date: 
Message-ID: <rNOSPAMon-5212C7.09424014072006@news.gha.chartermi.net>
In article <·············@individual.net>,
 Pascal Costanza <··@p-cos.net> wrote:

> Sure, but ((foo)) is not specified to be a compile-time error.

I should probably clarify something: in this case I'm not really 
concerned about ((foo)) specifically.  That was just a stand-in for my 
real concern, which is the following case:

? (defmacro foo () t)
FOO
? (defun baz () (function foo))
> Error: While compiling BAZ :
>        FUNCTION can't be used to reference lexically visible macro FOO.
> Type Command-. to abort.
See the Restarts� menu item for further choices.
1 > 

My real question is: is this a bug in the implementation?  I think it is 
because FOO could be redefined as a function before BAZ is called.

There's also a more general question: is there any way in CL for a macro 
to catch a compiler error at macro expansion time?  In other words, is 
it possible to write a macro that essentially says, "Try this code 
snippet, and if it doesn't compile properly in the current lexical 
context, try this other code snippet instead."?

rg
From: Pascal Costanza
Subject: Re: What should (ignore-errors (function foo)) do
Date: 
Message-ID: <4hq2ojFq4reU1@individual.net>
Ron Garret wrote:
> In article <·············@individual.net>,
>  Pascal Costanza <··@p-cos.net> wrote:
> 
>> Sure, but ((foo)) is not specified to be a compile-time error.
> 
> I should probably clarify something: in this case I'm not really 
> concerned about ((foo)) specifically.  That was just a stand-in for my 
> real concern, which is the following case:
> 
> ? (defmacro foo () t)
> FOO
> ? (defun baz () (function foo))
>> Error: While compiling BAZ :
>>        FUNCTION can't be used to reference lexically visible macro FOO.
>> Type Command-. to abort.
> See the Restarts� menu item for further choices.
> 1 > 
> 
> My real question is: is this a bug in the implementation?  I think it is 
> because FOO could be redefined as a function before BAZ is called.

RTFM: "It is an error to use function on a function name that does not 
denote a function in the lexical environment in which the function form 
appears. Specifically, it is an error to use function on a symbol that 
denotes a macro or special form. An implementation may choose not to 
signal this error for performance reasons, but implementations are 
forbidden from defining the failure to signal an error as a useful 
behavior."

So there is even no guarantee that you get an error at all. You're on 
your own here.

> There's also a more general question: is there any way in CL for a macro 
> to catch a compiler error at macro expansion time?  In other words, is 
> it possible to write a macro that essentially says, "Try this code 
> snippet, and if it doesn't compile properly in the current lexical 
> context, try this other code snippet instead."?

I don't think so. I don't think it's a good idea either. It would make 
the semantics of your macros rather accidental. (Consider that the 
compile-time error doesn't originate in the generated code, but in the 
one that was passed to a macro.)


Pascal

-- 
My website: http://p-cos.net
Closer to MOP & ContextL:
http://common-lisp.net/project/closer/
From: Ron Garret
Subject: Re: What should (ignore-errors (function foo)) do
Date: 
Message-ID: <rNOSPAMon-87202A.11061914072006@news.gha.chartermi.net>
In article <·············@individual.net>,
 Pascal Costanza <··@p-cos.net> wrote:

> Ron Garret wrote:
> > In article <·············@individual.net>,
> >  Pascal Costanza <··@p-cos.net> wrote:
> > 
> >> Sure, but ((foo)) is not specified to be a compile-time error.
> > 
> > I should probably clarify something: in this case I'm not really 
> > concerned about ((foo)) specifically.  That was just a stand-in for my 
> > real concern, which is the following case:
> > 
> > ? (defmacro foo () t)
> > FOO
> > ? (defun baz () (function foo))
> >> Error: While compiling BAZ :
> >>        FUNCTION can't be used to reference lexically visible macro FOO.
> >> Type Command-. to abort.
> > See the RestartsS� menu item for further choices.
> > 1 > 
> > 
> > My real question is: is this a bug in the implementation?  I think it is 
> > because FOO could be redefined as a function before BAZ is called.
> 
> RTFM: "It is an error to use function on a function name that does not 
> denote a function in the lexical environment in which the function form 
> appears.

The spec contradicts itself on this point by saying:

"Otherwise the global functional definition of the function name is 
returned."  The global environment in CL is distinct from the lexical 
environment.

> Specifically, it is an error to use function on a symbol that 
> denotes a macro or special form.

Sure, but it doesn't say that this has to be a compile-time error.

Consider:

(defun foo () 1)
(defun baz () (funcall (function foo)))
(defun foo () 2)
(baz)

AFAIK all CL implementations will return 1, but I don't think you can 
actually justify this in terms of the spec.


> So there is even no guarantee that you get an error at all. You're on 
> your own here.

Yes, that's how it appears.  That's unfortunate IMHO.


> > There's also a more general question: is there any way in CL for a macro 
> > to catch a compiler error at macro expansion time?  In other words, is 
> > it possible to write a macro that essentially says, "Try this code 
> > snippet, and if it doesn't compile properly in the current lexical 
> > context, try this other code snippet instead."?
> 
> I don't think so. I don't think it's a good idea either. It would make 
> the semantics of your macros rather accidental. (Consider that the 
> compile-time error doesn't originate in the generated code, but in the 
> one that was passed to a macro.)

I don't understand the referent of "the one that was passed to a macro."  
But here's an example of where this sort of thing might be useful:

(defmacro foo (...)
  (some-hypothetical-special-form-that-tries-code-snippets-
     in-sequence-until-one-compiles-successfully
     `(... (function baz) ...)
     (progn
        (warn "Using default fbinding for BAZ")
        `(flet ((baz (...) ...))
            (foo ...)))))

rg
From: Pascal Bourguignon
Subject: Re: What should (ignore-errors (function foo)) do
Date: 
Message-ID: <87mzbcxc8r.fsf@thalassa.informatimago.com>
Ron Garret <·········@flownet.com> writes:
> Consider:
>
> (defun foo () 1)
> (defun baz () (funcall (function foo)))
> (defun foo () 2)
> (baz)
>
> AFAIK all CL implementations will return 1, but I don't think you can 
> actually justify this in terms of the spec.

You mean 2, I assume.  (both clisp and sbcl return 2).

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

"Logiciels libres : nourris au code source sans farine animale."
From: Ron Garret
Subject: Re: What should (ignore-errors (function foo)) do
Date: 
Message-ID: <rNOSPAMon-D3BB1F.15020814072006@news.gha.chartermi.net>
In article <··············@thalassa.informatimago.com>,
 Pascal Bourguignon <···@informatimago.com> wrote:

> Ron Garret <·········@flownet.com> writes:
> > Consider:
> >
> > (defun foo () 1)
> > (defun baz () (funcall (function foo)))
> > (defun foo () 2)
> > (baz)
> >
> > AFAIK all CL implementations will return 1, but I don't think you can 
> > actually justify this in terms of the spec.
> 
> You mean 2, I assume.  (both clisp and sbcl return 2).

Yes.  See my response to Pascal for further elaboration.

rg
From: Pascal Costanza
Subject: Re: What should (ignore-errors (function foo)) do
Date: 
Message-ID: <4hq7akFqgj6U1@individual.net>
Ron Garret wrote:
> In article <·············@individual.net>,
>  Pascal Costanza <··@p-cos.net> wrote:
> 
>> Ron Garret wrote:
>>> In article <·············@individual.net>,
>>>  Pascal Costanza <··@p-cos.net> wrote:
>>>
>>>> Sure, but ((foo)) is not specified to be a compile-time error.
>>> I should probably clarify something: in this case I'm not really 
>>> concerned about ((foo)) specifically.  That was just a stand-in for my 
>>> real concern, which is the following case:
>>>
>>> ? (defmacro foo () t)
>>> FOO
>>> ? (defun baz () (function foo))
>>>> Error: While compiling BAZ :
>>>>        FUNCTION can't be used to reference lexically visible macro FOO.
>>>> Type Command-. to abort.
>>> See the RestartsS� menu item for further choices.
>>> 1 > 
>>>
>>> My real question is: is this a bug in the implementation?  I think it is 
>>> because FOO could be redefined as a function before BAZ is called.
>> RTFM: "It is an error to use function on a function name that does not 
>> denote a function in the lexical environment in which the function form 
>> appears.
> 
> The spec contradicts itself on this point

No, it doesn't.

> by saying:
> 
> "Otherwise the global functional definition of the function name is 
> returned."  The global environment in CL is distinct from the lexical 
> environment.

...but see 3.1.1.3: "Within a given namespace, a name is said to be 
bound in a lexical environment if there is a binding associated with its 
name in the lexical environment or, if not, there is a binding 
associated with its name in the global environment."

>> Specifically, it is an error to use function on a symbol that 
>> denotes a macro or special form.
> 
> Sure, but it doesn't say that this has to be a compile-time error.

...and neither does it disallow it to be a compile-time error.

> Consider:
> 
> (defun foo () 1)
> (defun baz () (funcall (function foo)))
> (defun foo () 2)
> (baz)
> 
> AFAIK all CL implementations will return 1, but I don't think you can 
> actually justify this in terms of the spec.

I am not 100% sure what you are referring to here. 3.2.2.3 states that a 
"call within a file to a named function that is defined in the same file 
refers to that function, unless that function has been declared 
notinline. The consequences are unspecified if functions are redefined 
individually at run time or multiply defined in the same file."

When I type the code into the listener, all CL implementations that are 
available to me return 2. (i.e., allegro, clisp, cmucl, ecl, lispworks, 
mcl, openmcl, sbcl)

>> So there is even no guarantee that you get an error at all. You're on 
>> your own here.
> 
> Yes, that's how it appears.  That's unfortunate IMHO.

What you seem to be looking for was actually partially covered in CLtL2 
- see the accessors for environment objects, like variable-information, 
function-information, etc. Allegro has a (modified) implementation of 
that interface. However, it is only fully supported for compiled code. 
But maybe that's good enough for your experiments.

>>> There's also a more general question: is there any way in CL for a macro 
>>> to catch a compiler error at macro expansion time?  In other words, is 
>>> it possible to write a macro that essentially says, "Try this code 
>>> snippet, and if it doesn't compile properly in the current lexical 
>>> context, try this other code snippet instead."?
>> I don't think so. I don't think it's a good idea either. It would make 
>> the semantics of your macros rather accidental. (Consider that the 
>> compile-time error doesn't originate in the generated code, but in the 
>> one that was passed to a macro.)
> 
> I don't understand the referent of "the one that was passed to a macro."  
> But here's an example of where this sort of thing might be useful:
> 
> (defmacro foo (...)
>   (some-hypothetical-special-form-that-tries-code-snippets-
>      in-sequence-until-one-compiles-successfully
>      `(... (function baz) ...)
>      (progn
>         (warn "Using default fbinding for BAZ")
>         `(flet ((baz (...) ...))
>             (foo ...)))))

Consider this:

(defmacro with-foo (&body body)
   (try-code
     `(let ((*foo* ((foo)))) ,@body)
     `(let ((*foo* 42)) ,@body)
     `(print "screw you")))

Do you want the result of this macro depend on whether body contains 
compile-time errors or not?


Pascal

-- 
My website: http://p-cos.net
Closer to MOP & ContextL:
http://common-lisp.net/project/closer/
From: Ron Garret
Subject: Re: What should (ignore-errors (function foo)) do
Date: 
Message-ID: <rNOSPAMon-B54FA7.15013214072006@news.gha.chartermi.net>
In article <·············@individual.net>,
 Pascal Costanza <··@p-cos.net> wrote:

> Ron Garret wrote:
> > In article <·············@individual.net>,
> >  Pascal Costanza <··@p-cos.net> wrote:
> > 
> >> Ron Garret wrote:
> >>> In article <·············@individual.net>,
> >>>  Pascal Costanza <··@p-cos.net> wrote:
> >>>
> >>>> Sure, but ((foo)) is not specified to be a compile-time error.
> >>> I should probably clarify something: in this case I'm not really 
> >>> concerned about ((foo)) specifically.  That was just a stand-in for my 
> >>> real concern, which is the following case:
> >>>
> >>> ? (defmacro foo () t)
> >>> FOO
> >>> ? (defun baz () (function foo))
> >>>> Error: While compiling BAZ :
> >>>>        FUNCTION can't be used to reference lexically visible macro FOO.
> >>>> Type Command-. to abort.
> >>> See the RestartsS? menu item for further choices.
> >>> 1 > 
> >>>
> >>> My real question is: is this a bug in the implementation?  I think it is 
> >>> because FOO could be redefined as a function before BAZ is called.
> >> RTFM: "It is an error to use function on a function name that does not 
> >> denote a function in the lexical environment in which the function form 
> >> appears.
> > 
> > The spec contradicts itself on this point
> 
> No, it doesn't.
> 
> > by saying:
> > 
> > "Otherwise the global functional definition of the function name is 
> > returned."  The global environment in CL is distinct from the lexical 
> > environment.
> 
> ...but see 3.1.1.3: "Within a given namespace, a name is said to be 
> bound in a lexical environment if there is a binding associated with its 
> name in the lexical environment or, if not, there is a binding 
> associated with its name in the global environment."

Damn you language lawyers.

Still, this definition strikes me as perverse.  IMHO "bound in a lexical 
environment" ought to mean just what it says.

> >> Specifically, it is an error to use function on a symbol that 
> >> denotes a macro or special form.
> > 
> > Sure, but it doesn't say that this has to be a compile-time error.
> 
> ...and neither does it disallow it to be a compile-time error.

True.  However, wouldn't you be annoyed if your lisp did this:

? (defun baz () (funcall #'snoz))
> Error: Undefined function: SNOZ
> While executing: CCL::%FUNCTION
> Type Command-. to abort.
See the Restarts� menu item for further choices.
1 > 

instead of this:

? (defun baz () (funcall #'snoz))
;Compiler warnings :
;   Undefined function SNOZ, in BAZ.
BAZ

> > Consider:
> > 
> > (defun foo () 1)
> > (defun baz () (funcall (function foo)))
> > (defun foo () 2)
> > (baz)
> > 
> > AFAIK all CL implementations will return 1, but I don't think you can 
> > actually justify this in terms of the spec.

For the record, I meant "2", not "1".  (The point being not the 
particular result, but rather that all implementations agree on the 
semantics despite (I claim) being underspecified in the spec.)

> I am not 100% sure what you are referring to here. 3.2.2.3 states that a 
> "call within a file to a named function that is defined in the same file 

Who said anything about files?

> refers to that function, unless that function has been declared 
> notinline. The consequences are unspecified if functions are redefined 
> individually at run time or multiply defined in the same file."

But that is in the context of a section on compilation.  My original 
question was generic, not specific to compilation.  (One of the tenets 
of CL is that the semantics of compiled code are supposed to be, to the 
extent possible, the same as interpreted code, no?)


> When I type the code into the listener, all CL implementations that are 
> available to me return 2. (i.e., allegro, clisp, cmucl, ecl, lispworks, 
> mcl, openmcl, sbcl)

Yes.  See above.

> >> So there is even no guarantee that you get an error at all. You're on 
> >> your own here.
> > 
> > Yes, that's how it appears.  That's unfortunate IMHO.
> 
> What you seem to be looking for was actually partially covered in CLtL2 
> - see the accessors for environment objects, like variable-information, 
> function-information, etc. Allegro has a (modified) implementation of 
> that interface. However, it is only fully supported for compiled code. 
> But maybe that's good enough for your experiments.

Certainly.  But I was hoping to be able to go beyond experiments and 
produce a portable implementation that people could actually use.

> >>> There's also a more general question: is there any way in CL for a macro 
> >>> to catch a compiler error at macro expansion time?  In other words, is 
> >>> it possible to write a macro that essentially says, "Try this code 
> >>> snippet, and if it doesn't compile properly in the current lexical 
> >>> context, try this other code snippet instead."?
> >> I don't think so. I don't think it's a good idea either. It would make 
> >> the semantics of your macros rather accidental. (Consider that the 
> >> compile-time error doesn't originate in the generated code, but in the 
> >> one that was passed to a macro.)
> > 
> > I don't understand the referent of "the one that was passed to a macro."  
> > But here's an example of where this sort of thing might be useful:
> > 
> > (defmacro foo (...)
> >   (some-hypothetical-special-form-that-tries-code-snippets-
> >      in-sequence-until-one-compiles-successfully
> >      `(... (function baz) ...)
> >      (progn
> >         (warn "Using default fbinding for BAZ")
> >         `(flet ((baz (...) ...))
> >             (foo ...)))))
> 
> Consider this:
> 
> (defmacro with-foo (&body body)
>    (try-code
>      `(let ((*foo* ((foo)))) ,@body)
>      `(let ((*foo* 42)) ,@body)
>      `(print "screw you")))
> 
> Do you want the result of this macro depend on whether body contains 
> compile-time errors or not?

Sure.  Why not?  I can even imagine a practical application:

(defmacro with-guaranteed-safety (&body body)
  (try-code `(let ((*readtable* +safe-readtable+))
               (ignore-runtime-errors ,@body))
            `(print "invalid code")))

(defun safe-server ()
  (loop
    (let ((forms (get-forms-from-external-input)))
      (eval `(with-guaranteed-safety ,@forms)))))

And if you don't like that example there's this one:

(defmacro my-function (thing)
  (try-code
    `(function ,thing)
    `(lookup-in-current-first-class-global-lexical-environment ,thing)))

rg
From: Pascal Costanza
Subject: Re: What should (ignore-errors (function foo)) do
Date: 
Message-ID: <4hrdruFur4pU1@individual.net>
Ron Garret wrote:
> In article <·············@individual.net>,
>  Pascal Costanza <··@p-cos.net> wrote:
> 
>> Ron Garret wrote:

>>> The spec contradicts itself on this point
>> No, it doesn't.
>>
>>> by saying:
>>>
>>> "Otherwise the global functional definition of the function name is 
>>> returned."  The global environment in CL is distinct from the lexical 
>>> environment.
>> ...but see 3.1.1.3: "Within a given namespace, a name is said to be 
>> bound in a lexical environment if there is a binding associated with its 
>> name in the lexical environment or, if not, there is a binding 
>> associated with its name in the global environment."
> 
> Damn you language lawyers.
> 
> Still, this definition strikes me as perverse.  IMHO "bound in a lexical 
> environment" ought to mean just what it says.

...but it means what it just says. ;)

>>>> Specifically, it is an error to use function on a symbol that 
>>>> denotes a macro or special form.
>>> Sure, but it doesn't say that this has to be a compile-time error.
>> ...and neither does it disallow it to be a compile-time error.
> 
> True.  However, wouldn't you be annoyed if your lisp did this:
[...]

Probably. But I have lost track why this is relevant.

>>> Consider:
>>>
>>> (defun foo () 1)
>>> (defun baz () (funcall (function foo)))
>>> (defun foo () 2)
>>> (baz)
>>>
>>> AFAIK all CL implementations will return 1, but I don't think you can 
>>> actually justify this in terms of the spec.
> 
> For the record, I meant "2", not "1".  (The point being not the 
> particular result, but rather that all implementations agree on the 
> semantics despite (I claim) being underspecified in the spec.)
> 
>> I am not 100% sure what you are referring to here. 3.2.2.3 states that a 
>> "call within a file to a named function that is defined in the same file 
> 
> Who said anything about files?

I was just guessing. As I said, it wasn't clear to me what you have been 
referring to. The important thing here is that this case is not 
underspecified.

>> What you seem to be looking for was actually partially covered in CLtL2 
>> - see the accessors for environment objects, like variable-information, 
>> function-information, etc. Allegro has a (modified) implementation of 
>> that interface. However, it is only fully supported for compiled code. 
>> But maybe that's good enough for your experiments.
> 
> Certainly.  But I was hoping to be able to go beyond experiments and 
> produce a portable implementation that people could actually use.

I am getting a little tired of this kind of discussion. So I am going 
meta here.

There are essentially two ways to go: You can either spend another 
several days lamenting the fact that Common Lisp doesn't quite do what 
you expect it to do, or you could pick one of the next best solutions 
and be eventually surprised that they work better than you currently 
expect. It's your choice.

My suggestion would be to shadow flet, labels, etc., and encode the 
information you need yourself in symbol macros. The only (mild) 
restriction is that this requires all code that wants to use your module 
system to be recompiled using your new definitions. But changes to 
existing code are probably required anyway, so that's less of a burden 
than you seem to think anyway. (The addition of a module system is a 
pretty deep change of a language.)



Pascal

-- 
My website: http://p-cos.net
Closer to MOP & ContextL:
http://common-lisp.net/project/closer/
From: Leonid Slobodov
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <44b7600b$0$6691$9b4e6d93@newsread4.arcor-online.net>
Pascal Costanza wrote:

> Sure, but ((foo)) is not specified to be a compile-time error.
> 
> 
> 
> Pascal
> 

Yes, but many of people (not specifically you) here have been arguing to
death that (ignore-errors ((foo))) should catch the error, should one 
be signaled by the implementation (as is often done).
From: Kent M Pitman
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <uzmfcjl6d.fsf@nhplace.com>
Leonid Slobodov <······@thedoghousemail.com> writes:

> Pascal Costanza wrote:
> 
> > Maybe I misunderstood your previous posting, but it seems to state that
> > (ignore-errors ((foo))) should be an error at compile time. If this is
> > not what you said, I am sorry that I have misunderstood you.
> > 
> > Nevertheless, I am not so sure whether your criterion is really that
> > clear cut. Consider this:
> > 
> > (defun foo () (/ 1 0))
> > 
> > This function will always fail at runtime, and this can already be
> > detected at compile time. (Common Lisp disallows changing the definition
> > of /.)

Right. The CMU compiler might well compile this the same as

 (defun foo () (error ...))

> > There is no "natural" reason why some of these things are compile-time
> > errors and others are not. These are "just" (hopefully specified)
> > conventions.

Well, there's a natural sense in which errors are appropriate to the time
at which they are noticed.  It's not inconceivable for an error to be a
compile-time error but not be noticed until runtime--an interpreter has
exactly that situation.  It is effectively doing what people now might call
JIT compilation, and so the notion of compile-time is distributed about over
time, right into the execution.

So, properly, there is no natural reason why these are "necessarily"
compile-time (in the sense of Saul Kripke, 
  http://en.wikipedia.org/wiki/Saul_Kripke
and "necessary truth"), but whatever time they are happens for reasons
of nature, and so has a natural reason in some sense. (There's also a
body of literature on "natural concepts", starting from Osherson and 
Smith; I was lucky enough to have Osherson as an instructor in college.
It's interesting stuff, and worth digging out, but but relating it
directly here is more than I'm up to.)

> All of that is fine, but I always thought that (ignore-errors foo)
> does an equivalent of (handler-bind foo (error (c) (values nil c)).
> This clearly has runtime semantics.
> It would probably cause serious breakage if this form would suddenly
> catch compile-time errors.

I think the spec is ambiguous on this point, since you don't know when
it will do lexical analysis--before or after runtime.

There was a similar HUGE rat's nest about COMPILER-LET which is why it
went away between CLTL and ANSI CL...

> Another thing is (ignore-errors (compile nil '(lambda () ((foo))))).
> ((foo))'s compile-time is the runtime of ignore-errors, thus the error
> is caught. 

If it's signaled then, yes.

Go ahead and put IGNORE-ERRORS around a call to COMPILE but not because
you plan to trap errors, just because you don't want errors to stop you
dead in the water. It's a subtle but important distinction.

- - - -

More generally:

The whole key to the CL condition system is to understand that it is not
Java.  (This is an anachronistic explanation, since it relies almost on
reverse causality to make sense, but it's the short way of making my point.)
We do not pretend you can enumerate all errors that a function will have.
Rather, we assume that at any time, any function may signal any error.

"Any function???" I hear you asking.  Well, yes.  Let's take something like
EQL.  The function itself will not, of course, but it's certainly possible
to take an interrupt during its execution, and the interrupt handler can
run code, and that code can signal an error, and that error will be seen
on the thread that the EQ was running in and be visible to the surrounding
code, as if EQ had signaled it.  Probably no one will expect this, so it 
will fall through to an outer handler, which in turn won't care that it was
inside of EQ, so no one thinks of it that way.  But the point is that claims
that certain functions never signal an error only make useful sense if you
lock out interrupts, which is beyond the scope of CL.  Of course, you can
say since interrupts don't exist in CL, you shouldn't be fettered with them.
And your vendor will say fine, if you like running without interrupts, go
ahead.  But you won't stay in that mode long before you accept that most
CL's run in a mode that is extended to accomodate other issues that are 
beyond the scope of the standard... and not just because we didn't think
of them--we had interrupts back then. We had GC, too, but we didn't write
that into the standard either, and you're welcome to run without a GC if
you like. :)

But when designing CL's error system, which I did largely by studying the
New Error System (NES) for Symbolics sometime around 1984, if I recall
correctly--it's probably a matter of record, so trust the record, not
this post--I talked to Dave Moon about what advice he had about 
articulating stuff like this.  I was going to copy all the very detailed
conditions that NES had offered, which included the ability to detect
refined things like missing catch tags vs missing go tags, and whatnot.
He recommended not to.  This is one of the only times he ever told me not
to take a LispM feature, so I recall it clearly.  He said that experience
showed that it wasn't useful, and that any program that was actually trying
to handle those errors was pretty darned suspect anyway... So he 
recommended we go with just vague things like PROGRAM-ERROR and wait for
communities to find the need.  And I must say, implementing ((foo)) is
not an example of such a need--it's an example of someone asking for
a different feature entirely and when they don't get it, just trying to
shoehorn it in through the back door.  Language design should not proceed
that way.  I'm not trying to answer the legitimacy of the ((foo)) issue;
I'm saying that even if a legitimate request, error handling is not the fix
if you don't get it through proper politics.  That just opens a precedent
for lousy design that will ultimately unravel the language.
From: Marcin 'Qrczak' Kowalczyk
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <87hd1kcsmd.fsf@qrnik.zagroda>
Pascal Costanza <··@p-cos.net> writes:

>> Why to leave the semantics ambiguous in this respect?
>
> Maybe I misunderstood your previous posting, but it seems to state
> that (ignore-errors ((foo))) should be an error at compile time.

Indeed it should.

> (defun foo () (/ 1 0))
>
> This function will always fail at runtime, and this can already be
> detected at compile time.

Division by zero in general is detected dynamically. Rules about
statically valid programs are more consistent when it's always treated
as a dynamic error, rather than sometimes as static and sometimes as
dynamic.

Well-defined rules about static validity allows macros to decide in
which cases they are allowed to produce suspicious code which happens
to be on a dead path. If too much code is statically valid, then
genuine bugs are detected later than they could. If too little code is
statically valid, then macros must be more careful with producing code
which avoids nonsensical paths only at runtime, e.g. beta-reduction
could be invalid. The criterion about the kind of error which is
always detectable without running the code seems to be a natural
guideline for me.

> (defun bar ()
>    (if nil x 42))
>
> Let's assume that x is not globally defined. So we have a free
> variable, but the code would always succeed anyway.

The claim that it succeeds makes a hidden assumption that it's valid
code at all. Since lexical variables are matched with their definitions
statically, it's natural to signal this error at the same time.


"Nathan Baum" <···········@btinternet.com> writes:

> I think the real question is whether or not the developer is to be
> _prohibited_ from writing invalid forms which are never executed,
> or merely _sternly warned_ about it.

The current practice is to reject some forms. The question is whether
each implementation should decide itself what to reject, or whether
static validity should be a portable concept (ignoring non-portable
features used in the intended way).

>> Well, this is one of things I hate in Lisp: too many aspects are
>> unspecified, in particular those regarding phases of execution
>> (what is visible in which environment, when errors are signalled).
>
> I don't think Lisp _has_ phases of execution.

See EVAL-WHEN. See various environments in
<http://www.lisp.org/HyperSpec/Body/sec_3-2-1.html>.

There are too many occurrences of "might" on that page, e.g.
"the compilation environment and evaluation environment might be
identical", "the startup environment and evaluation environment might
be identical", "For example, when compiling a file, the definition of
a function might be retained in the compilation environment if it is
declared inline. This definition might not be available in the
evaluation environment".

> New source can be loaded and compiled on a running system.

Runtime of some code may include compile time of another code
(and even static errors from compilation of the other code may
become dynamic errors of the calling code). This is compatible
with the desire to clearly define which errors are detected at
which phases, and with phase separation of each single piece
of code.

-- 
   __("<         Marcin Kowalczyk
   \__/       ······@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/
From: Pascal Costanza
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <4hnr64Ffv4sU2@individual.net>
Marcin 'Qrczak' Kowalczyk wrote:
> Ron Garret <·········@flownet.com> writes:
> 
>> What should (ignore-errors ((foo))) do?
> 
> It should be an error. IGNORE-ERRORS catches evaluation (runtime)
> errors, not compilation errors.
> 
> Perhaps Lisp doesn't separate these kinds of errors as well as it
> should.

Based on what criterion should Lisp do this?


Pascal

-- 
3rd European Lisp Workshop
July 3 - Nantes, France - co-located with ECOOP 2006
http://lisp-ecoop06.bknr.net/
From: Kent M Pitman
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <u4pxkl0wn.fsf@nhplace.com>
Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:

> Ron Garret <·········@flownet.com> writes:
> 
> > What should (ignore-errors ((foo))) do?
> 
> It should be an error. IGNORE-ERRORS catches evaluation (runtime)
> errors, not compilation errors.

In some situations, such as execution of interpreted code, those are
the same, which is why it confuses people.  But yes, this is a correct
analysis of the intent, although slightly incomplete as to its subtlety.
(I'll continue my remarks on this in another post that adds the necessary
context.)

> Perhaps Lisp doesn't separate these kinds of errors as well as it
> should.

The problem isn't errors, the problem is environments (both storage and
control).  There was so much divergence among existing implementations
when the standard was created (and probably still today) that it was 
beyond the scope of the project to force a particular behavior.  

The reason for that is, when you peel it back, partly antitrust law.
Standards are consensus-making bodies, but standards-making bodies are
phobic of creating standards that create huge amounts of cost to
someone affected while not creating equivalent cost to others, since
this can put one business out of business.  

But even in the most conservative reading of the meta-problem, if you
create a standard that says "this requires you to only use
implementations that have an outboard compiler in its own wholly
separated environment", then in practice you create a void for a
competing standard to make utterly different choices and to serve the
market you have said you won't serve.  The way you are encouraged to
serve whole communities is to understand that when you lock someone out,
you lose their market share.

So, for example, CL knew it was losing some market share by not being
Scheme-compatible.  That was discussed intensely, and it was decided in
many side discussions, though never by formal vote, that both communities
would be happier if we didn't force them together.  That isn't to say
we didn't add some features for cross-compatibility (like removing the
#' requirement before LAMBDA), but we didn't make it a primary goal to
serve that community's other needs.
From: Rob Warnock
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <o7idnZVlLIoI-iXZnZ2dnUVZ_rqdnZ2d@speakeasy.net>
Kent M Pitman  <······@nhplace.com> wrote:
+---------------
| The reason for that is, when you peel it back, partly antitrust law.
| Standards are consensus-making bodies, but standards-making bodies are
| phobic of creating standards that create huge amounts of cost to
| someone affected while not creating equivalent cost to others, since
| this can put one business out of business.  
+---------------

Unfortunately, I fear this is part of the reason that in networking
standards, for example, beginning roughly about the beginning of
the FDDI standardization process, standards bodies stopped allowing
themselves to standardize "best existing practice" [which had been
the previous expectation and practice, such as for the standards
for HIPPI, Ethernet, and IEEE-488], and instead insisted on only
considering *brand-new* designs [such as FDDI] that no-one had ever
implemented yet, in order to ensure "maximal mutual disadvantage"
[my term for it] among all of the competing parties. As a result,
we've ended up with monstrosities such as FDDI, ATM, InfiniBand, etc.
(*Feh!*)


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Kent M Pitman
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <uzmfa6g98.fsf@nhplace.com>
····@rpw3.org (Rob Warnock) writes:

> Kent M Pitman  <······@nhplace.com> wrote:
> +---------------
> | The reason for that is, when you peel it back, partly antitrust law.
> | Standards are consensus-making bodies, but standards-making bodies are
> | phobic of creating standards that create huge amounts of cost to
> | someone affected while not creating equivalent cost to others, since
> | this can put one business out of business.  
> +---------------
> 
> Unfortunately, I fear this is part of the reason that in networking
> standards, for example, beginning roughly about the beginning of
> the FDDI standardization process, standards bodies stopped allowing
> themselves to standardize "best existing practice" [which had been
> the previous expectation and practice, such as for the standards
> for HIPPI, Ethernet, and IEEE-488], and instead insisted on only
> considering *brand-new* designs [such as FDDI] that no-one had ever
> implemented yet, in order to ensure "maximal mutual disadvantage"
> [my term for it] among all of the competing parties. As a result,
> we've ended up with monstrosities such as FDDI, ATM, InfiniBand, etc.
> (*Feh!*)

FWIW, I think there was always a bit of this, it's just cloaked in
different ways.  To some extent, you have CLOS rather than Flavors for
the equivalent reason.  Many consider it an improvement, but some don't.
And it could be that in the alternate timeline where Flavors had won,
although we wouldn't have multimethods and the MOP (two plainly fine
achievements), we might be more compatible with the JVM and the CLR 
because our object model would not be so far afield.

But I take your point.  The observation made by the standards folks from
then-NBS (now NIST) when we started was that standards groups ought not
be doing design.  That is, you should arrive with near consensus when you
start and be ready to hammer out details.  If you don't, you're using a
set of rules that are simply not designed to cope with the complexity of
standards in the best way--that is, in a coherent way.  

I've never quite worked it through in rigorous enough detail to be
sure, but my sense is that a democracy has the computational power of
(and classical problems of) a perceptron.  That is, because it simply
adds the votes, and because it doesn't allow one vote to be contingent
on another, it isn't capable of operating in the kind of coordinated
way necessary to represent complicated patterns that require internal
consistency in order to assure operational correctness.  If my
analysis is right, that's why we have a government that's increasingly
incoherent over time, even though I'd bet a majority of voters would
prefer consistency.  (I mention democracy in this context because the
existing consensus bodies, like ANSI, seem to define consensus to be
implemented by a vote... and that's the problem.  My understanding is
that the traditional notion of consensus is more broad and allows for
more complicated bargaining--at the expense that perhaps either the
voting process itself can deadlock or someone has to be appionted
master controller to break deadlocks, which is why most standards
groups don't try that.)
From: Robert Uhl
Subject: Re: What should (ignore-errors ((foo))) do?
Date: 
Message-ID: <m33bd2jkc7.fsf@NOSPAMgmail.com>
Kent M Pitman <······@nhplace.com> writes:
>
> I've never quite worked it through in rigorous enough detail to be
> sure, but my sense is that a democracy has the computational power of
> (and classical problems of) a perceptron.  That is, because it simply
> adds the votes, and because it doesn't allow one vote to be contingent
> on another, it isn't capable of operating in the kind of coordinated
> way necessary to represent complicated patterns that require internal
> consistency in order to assure operational correctness.  If my
> analysis is right, that's why we have a government that's increasingly
> incoherent over time, even though I'd bet a majority of voters would
> prefer consistency.  (I mention democracy in this context because the
> existing consensus bodies, like ANSI, seem to define consensus to be
> implemented by a vote... and that's the problem.  My understanding is
> that the traditional notion of consensus is more broad and allows for
> more complicated bargaining--at the expense that perhaps either the
> voting process itself can deadlock or someone has to be appionted
> master controller to break deadlocks, which is why most standards
> groups don't try that.)

I'll have to ponder this for quite awhile, but I _think_ you've just
given me an excellent political idea...

-- 
Robert Uhl <http://public.xdi.org/=ruhl>
You can't enslave a free man.  Only person can do that to a man
is himself.  The most you can do to a free man is to kill him.
                                         --Robert A. Heinlein