[comp.lang.ada] Ada vs. LISP

eachus@mbunix.mitre.org (Robert Eachus) (03/07/89)

In article <7682@venera.isi.edu> raveling@vaxb.isi.edu (Paul Raveling) writes:
>In article <6153@medusa.cs.purdue.edu> rjh@cs.purdue.EDU (Bob Hathaway) writes:
>>...  Ada was designed to standardize software and it
>>could replace almost any language with exceptions being rare.
>
>	Have you suggested that to a hard-core LISP user lately?
>
>Paul Raveling
>Raveling@isi.edu

     One of the things which I did during the ANSI standardization of
Ada was to look for ANYTHING in the standard which would make
translation of LISP programs into Ada difficult.  There were a few
problems in the early drafts, but they were all eliminated by the
final draft.  As one of the problems for the AdaCan contest I proposed
writing a compatiblity package to allow transliterated Common LISP to
be compiled by any Ada compiler.  (There are certain LISP lexical
conventions that are incompatible with Ada, but they are easily dealt
with: 'a --> QUOTE(A).)  

     The problem was eliminated from the final list as too easy, but I
still recieved two proposed solutions from LISP and Ada programers I
showed the writeup to!  Not only can you write AdaLISP, but some
people already do.  Incidently, AdaLISP does look a lot like LISP with
the primary structures being nested fuction calls and aggregates, but
there is no easy way to close lots of scopes, so don't try it without
a good EMACS.

     It seems that everyone has seen AdaTRAN, but few people realize
that the capability to write FORTRAN or COBOL or Pascal or LISP style
programs in Ada was not an accident, it was a deliberate design
requirement.

					Robert I. Eachus

function TWIDDLE_THUMBS (LEFT, RIGHT: THUMB) return THUMBS is
  begin return TWIDDLE_THUMBS(RIGHT, LEFT); end TWIDDLE_THUMBS;

rar@ZOOKS.ADS.COM (Bob Riemenschneider) (03/09/89)

=>   From: eachus@mbunix.mitre.org (Robert Eachus)
=>
=>	One of the things which I did during the ANSI standardization of
=>   Ada was to look for ANYTHING in the standard which would make
=>   translation of LISP programs into Ada difficult.  There were a few
=>   problems in the early drafts, but they were all eliminated by the
=>   final draft.  As one of the problems for the AdaCan contest I proposed
=>   writing a compatiblity package to allow transliterated Common LISP to
=>   be compiled by any Ada compiler.  (There are certain LISP lexical
=>   conventions that are incompatible with Ada, but they are easily dealt
=>   with: 'a --> QUOTE(A).)  
=>
=>	The problem was eliminated from the final list as too easy, but I
=>   still recieved two proposed solutions from LISP and Ada programers I
=>   showed the writeup to! ...

Could you provide more detail?  Handling the "LISP 1.0 subset" is
straightforward.  But how, for example, would the program

			(apply (read) (read))

be written in AdaLISP?

							-- rar

tking@gumby.SRC.Honeywell.COM (Tim King) (03/10/89)

In article <45978@linus.UUCP> eachus@mbunix.mitre.org (Robert Eachus) writes:

>      One of the things which I did during the ANSI standardization of
> Ada was to look for ANYTHING in the standard which would make
> translation of LISP programs into Ada difficult.  There were a few
> problems in the early drafts, but they were all eliminated by the
> final draft. 
>   ...
> (There are certain LISP lexical conventions that are incompatible with
> Ada, but they are easily dealt with: 'a --> QUOTE(A).)

Now, I'm no world class Lisp hacker, but I do know Ada, and I know enough
about Lisp that I almost choked on my tongue when I read this.  I showed
this article to an associate who is heavily involved with Lisp (eg, as a
member of the ANSI Common Lisp standards committee, and as a longtime Lisp
zealot).  He suggested that you might consider the following points:

  1) Lisp's ability to store arbitrary objects in arrays regardless of
     the type of the object (ditto for lists, hash tables, etc.).
  2) The first class nature of functions in Lisp.
  3) Lisp's ability to share state among closures (you might be
     able to do this with Ada tasks).
  4) Lisp macros.
  5) Lisp symbols (they have plists and function bindings).
  6) Lisp's complex type specifiers (e.g. type foo is either an integer or
     an array).
  7) And so on.

In a nut shell Ada can't support Lisp's view of typing, and functions are
not first class objects in Ada.  Even if you could somehow solve these
problems, the performance of the resulting "AdaLisp" would be abysmal.

If you *really* don't have anything better to do, try to write the following
code in Ada:

  (defun funs (n)
    (let ((z n))
      (cons #'(lambda (x) (incf z x))
	    #'(lambda (x) (decf z x)))))

  (setq foo (funs 0))
  (funcall (car foo) 10)   =>  10
  (funcall (cdr foo) 3)    =>   7

(=> is a short hand for evaluates to, and is not part of Common Lisp)

-----------------------------------------------------------------
Tim King                             |
Honeywell Systems & Research Center  |  Are we having fun yet?
Mpls, MN  55418                      |

gateley@m2.csc.ti.com (John Gateley) (03/10/89)

In article <45978@linus.UUCP> eachus@mbunix (Robert I. Eachus) writes:
>     One of the things which I did during the ANSI standardization of
>Ada was to look for ANYTHING in the standard which would make
>translation of LISP programs into Ada difficult.

Hmmm.... how would the following programs be written in Ada:
(I give both Scheme and CL versions, take your pick)

Scheme                           CL
(define x                        (defun x (n)
  (lambda (n)                      (function (lambda (m)
    (lambda (m)                       (+ n m)))
      (+ m n))))

that is, how can you write first class functions? These are quite
useful for things like writing an interpreter for Lisp in Lisp, or
a denotational semantics, or table abstractions where the elements are
functions etc.

Scheme                           CL
(define print                    (defun print (x)
  (lambda (x)                      (typecase x
    (cond                            (integer 1)
      ((integer? x) 1)               (real 2)
      ((real? x) 2)                  (complex 3)
      ((complex? x) 3)               (vector 4)))
      ((vector? x) 4))))

that is, how can you write dynamically typed functions?

I do not think you can.
These two features of Lisp that I have highlighted are fundamental aspects
of the langauge. That is, it is not fair to say that you can translate
programs from Lisp to Ada unless you can handle these cases as well.
I am assuming that you do not mean you can write a Lisp compiler in Ada
(since you can do that in any language), but that you can translate
any expression in Lisp into a corresponding Ada fragment.

John
gateley@tilde.csc.ti.com

sdl@linus.UUCP (Steven D. Litvintchouk) (03/13/89)

In article <45978@linus.UUCP> eachus@mbunix.mitre.org (Robert Eachus) writes:

>     One of the things which I did during the ANSI standardization of
> Ada was to look for ANYTHING in the standard which would make
> translation of LISP programs into Ada difficult....
>      It seems that everyone has seen AdaTRAN, but few people realize
> that the capability to write FORTRAN or COBOL or Pascal or LISP style
> programs in Ada was not an accident, it was a deliberate design
> requirement.

Now how about Simula-67?  If only you had applied the same requirement
to translating Simula-67 programs to Ada, perhaps Ada might have
supported subclassing/inheritance better than it does!  Seems like a
missed opportunity....

In fact, the significance of Simula-67's class mechanism appears to
have been overlooked by nearly everyone connected with the DoD HOL
initiative--was it ever seriously considered for inclusion in
Steelman?  Or did they conclude (mistakenly) that types accomplished
exactly the same thing?


Steven Litvintchouk
MITRE Corporation
Bedford, MA  01730
Fone:  (617)271-7753
ARPA:  sdl@mitre-bedford.arpa
UUCP:  ...{att,decvax,genrad,ll-xn,philabs,utzoo}!linus!sdl
	"Those who will be able to conquer software will be able to
	 conquer the world."  -- Tadahiro Sekimoto, president, NEC Corp.

eachus@mbunix.mitre.org (Robert Eachus) (03/14/89)

     I recieved many responses to my posting about Lisp style
programming in Ada.  Some were a bit extreme--An Ada program which
supports the LISP semantics for (apply (read) (read)) is called a
LISP interpreter.  That is not what I was talking about.  Of course
you can write a LISP _interpreter_ in Ada, I was talking about
compilable Ada code derived from LISP programs or designs.

     Now that I have also recieved several civil responses asking
how to do it, it seems I had better post an example or two.  This
posting won't satisfy the skeptics, but then I could probably write
a book explaining all the details and not satisfy some of them.

     The first thing to realize is that, contrary to the way Ada
generics are usually taught, instantiation of generics happens during
program execution, and that each time the generic instantiation is
elaborated it creates a new instance. (If you think you understand
this, skip ahead to SKIP_TO_HERE:. But I warn you, most Ada
programmers only think they understand what that meant.)

     Those of you who are left, try this on your favorite Ada
compiler:

     generic
       type Element is private;
       type Index is range <>;
       type List is array(Index) of Element;
     function Reverse(L: List) return List;

     function Reverse(L: List) return List is
       R: List; -- OK since List is constrained;
     begin
       for I in L'RANGE loop
         R(I) := L(L'LAST - (I - L'FIRST));
       end loop;
       return R;
    end Reverse;

    There are more elegent ways to write this in Ada, but that is not
the point.  If you write a program to instantiate this generic in a
loop:

    with Text_IO; with Reverse; with Get;
    procedure Test is
    begin
      loop
        declare
          Foo: constant String := Get;
          subtype Foo_Index is Integer range Foo'FIRST..Foo'LAST;
          subtype Foo_Type is String(Foo_Index);
          function Backwards is new Reverse(Character, Foo_Index, Foo_Type);
        begin
          exit when Foo'LENGTH < 1;
          Put_Line(Backwards(Foo));
        end;
      end loop;
    end Test;

    On every pass through the loop, subtype Foo_Type has different
bounds.  Therefore each instance of Backwards expects a different
length string.  (Defining the function Get using TEXT_IO.GET_LINE is
left as an exercise for the reader.)

SKIP_TO_HERE:

    Now most of you are probably saying: "Big deal, we knew that Ada
allowed strings with non-static bounds...", but the big deal is that
subprograms are allowed as generic formals:

    generic
      type Element is private;
      type List is private;
      with function Something (E: in Element) return Element;
      with function "&"(Left: Element; Right: List) return List;
      with function CDR(L: in List) return List;
      with function CAR(L: in List) return Element;
      NUL: List
      -- Note: in a "real" lisp style Ada program only "Something"
      -- would be a generic parameter.
    function MAPCAR (L: in List) return List;

    function MAPCAR (L: in List) return List is
    begin
      if L = NUL then return NUL; end if;
      return Something(CAR(L)) & MAPCAR(CDR(L));
    end MAPCAR;

    Very useful, but not yet LISP.  We sometimes need to be able to
pass functions as objects.  Fortunately there is a way, but Ada
purists will scream:

    function MAPCAR (L: in List; F: SYSTEM.ADDRESS) return List is
      function Something (E: in Element) return Element;
      pragma INTERFACE(System, Something);
      for Something'ADDRESS use F;
    begin
      if L = NUL then return NUL; end if;
      return Something(CAR(L)) & MAPCAR(CDR(L));
    end MAPCAR;

    Obviously not guarenteed to be portable, but if your compiler
supports it, you don't even need to use generics to have (LISP) fun
in Ada.  (Just substitute whatever language name your compiler
requires for System in the pragma.  One or two even allow Ada!)

    The next level of completeness is to create a "real" LISP
environment.  It is very rare to need to go this far, but it is
possible: 

    package LISP is
      type Element is private;

      type List is  array (Natural range <>) of Element;
      -- Lists are defined as arrays so that (a,b,c) works. I usually
      -- cheat and provide visible arrays of Integers, and Float so
      -- that (1,2,3) and (1.0,2.0,3.0) can be recognized and
      -- handled.

     type Element_Type is (Number, Character, Symbol, List, Vector,
                    	   Structure, Function);
      -- You may wish to add others, but this is what I use.  Note
      -- that this is actually only provided as a shortcut for a
      -- special form of my own: 

      function IS_A(Object: Element; Class: Element_Type) return Boolean;

      function MAKE(I: Integer) return Element;
      function MAKE(C: Character) return Element;
      function MAKE(S: String) return Element;
      -- etc.

      NIL: constant Element;

      Apply: Element;
      Eval: Element;
      -- Through all the special forms you use...
    private
      type Object;
      type Element is access Object;
    end LISP;

    What about the package body?  It's fairly simple: Eval looks for a
predefined functions with a case statement, and otherwise follows the
standard (LISP) rules, and so on.  Defun (and this is what keeps
things from being unacceptably slow) actually does instantiation, and
keeps the defined form available for Eval (see above).  If pragma
INTERFACE didn't work, you could treat each new function as a new Ada
task object but I have had to stoop that low.  I prefer to make
available several generics in the specification of package LISP:

    generic
      with procedure X(L: List);
    package New_Procedure is
      New_X: Element;
    end package;

    New_X is, of course a new function object which can be Evaled,
and the semantics are to invoke (the Ada generic formal procedure) X
on the first argument.  (In this case it evals to nil, of course.)
This allows some functions (or in this case a procedure) to use Ada
semantics, and others to use LISP.

					Robert I. Eachus

rar@ZOOKS.ADS.COM (Bob Riemenschneider) (03/16/89)

Robert:

Thanks for posting the examples.  While they may not "satisfy the skeptics",
they make the details of your claims for AdaLISP considerably clearer.  It
now seems to me that most of the "extreme" reaction was due to a 
misinterpretation of your original claim.

=>	One of the things which I did during the ANSI standardization of
=>   Ada was to look for ANYTHING in the standard which would make
=>   translation of LISP programs into Ada difficult.  There were a few
=>   problems in the early drafts, but they were all eliminated by the
=>   final draft.  As one of the problems for the AdaCan contest I proposed
=>   writing a compatiblity package to allow transliterated Common LISP to
=>   be compiled by any Ada compiler.  (There are certain LISP lexical
=>   conventions that are incompatible with Ada, but they are easily dealt
=>   with: 'a --> QUOTE(A).)  
=>
=>	The problem was eliminated from the final list as too easy, but I
=>   still recieved two proposed solutions from LISP and Ada programers I
=>   showed the writeup to! ...

I now understand you to be claiming that the bulk of most Lisp application
programs can be easily rewritten in Ada given a fairly small collection of
fairly simple library packages.  I've had some experience porting Lisp
applications to Ada, and, based on that experience, I certainly agree.
(In fact, as your examples show, it's easier to "transliterate" Lisp into 
Ada than into, say, Pascal.) 

There are exceptions, however.  Based on your latest posting, I take it
you believe "(apply (read) (read))" to be a specially concocted example,
intended to make your claim sound dubious.  It wasn't; it was a (simplified) 
example taken from an actual Lisp application.  (The program supports
interactive multi-attribute utility analysis.  Rather than having the 
user supply weights used in a linear combination of utilities across
attributes, the user is asked for an arbitrary computable function from
[0,1]^number-of-attributes to [0,1] to be used for combination.  The
designer (me) has arguments that, for many applications, non-linearity
is required.)  When time for considering translation to another language
came around, "(apply (read) (read))"--which, when expanded out to include the
syntactic analysis of the sexpr read in, etc., made up a goodly chunk of
the program--was the only really hard part.  Writing a simple Lisp-interpreter
equivalent was evidently necessary, as you observed.  I asked about
"(apply (read) (read))" because I wanted to know whether either of the
AdaLISP submissions you received contained at least a simple interpreter
of the sort you sketch in your posting.  I still want to know.

I think if you re-read the passage I quoted above, you'll see that it
could be understood as saying that translation of virtually *any* Common 
Lisp program into Ada is easy, since you never explicitly restrict the class
of Lisp programs you're discussing.  The point of most of the "uncivil"
replies is that that's false, because some programs would require writing a 
Common Lisp interpreter in Ada, and writing a *Common* Lisp interpreter in 
any language is *hard*.  You seem to be well aware of this, and, perhaps
justifiably, to take offense at replies that suggest that you aren't.
On the other hand, Lisp proponents are ever more frequently having to
argue that *some* applications are orders of magnitude easier to
program in Lisp than in Ada, attempting to justify it's use to someone
who doesn't have any idea what Lisp is or why this is the case.  Every
time someone posts a message to comp.lang.ada that *can* be interpreted
as saying "there's never any significant advantage in using Lisp rather
than Ada", some people who do (or want to) believe that will take the
posting as evidence that that's the case.  So, you've made Lisp proponents'
lives more difficult, and some of them, understandably, got upset.  

You might have some disagreement with Lisp proponents as to which
applicaions are better coded in Lisp than Ada, but I think everyone
agrees that Lisp has no great advantage when it comes to simple list 
processing, and that it has a big advantage when a full-blown Common
Lisp interpreter is needed.  I'd be very interested in seeing Ada fans
address some of the features on Tim King's list, in the way that Mike
Linnig addressed John Gateley's dynamic typing example.

							-- rar

eachus@mbunix.mitre.org (Robert Eachus) (03/17/89)

In article <8903152108.AA06589@zooks.ads.com> rar@ZOOKS.ADS.COM (Bob Riemenschneider) writes:

>Thanks for posting the examples.  While they may not "satisfy the skeptics",
>they make the details of your claims for AdaLISP considerably clearer.  It
>now seems to me that most of the "extreme" reaction was due to a 
>misinterpretation of your original claim.

     Glad to be back in a rational discussion.

>There are exceptions, however.  Based on your latest posting, I take it
>you believe "(apply (read) (read))" to be a specially concocted example...
(lots deleted).

     No, I believe it is an example of a problem that requires an
interpreter.  If you use a compiler for such an application, you (as
you noted) end up writing your own interpreter.  This issue is
different from choice of language, although they are interdependant.
I have BASIC(ugh!, but a nice graphics interface), Scheme and APL
interpreters on my Amiga for that sort of stuff, and I am planning to
get Maple for more sophisticated math munging.  If the result is
something I need to encapsulate for others to use and (horrors)
maintain, I use a compiler, and usually a different language.  The
language switch is usually a non-issue, because a total rewrite is
required anyway.  If it isn't, it means that the requirements haven't
changed drastically and I can stay with an interpreted version.

					Robert I. Eachus

with STANDARD_DISCLAIMER;
use  STANDARD_DISCLAIMER;
function MESSAGE (TEXT: in CLEVER_IDEAS) return BETTER_IDEAS is...

pierson@mist (Dan Pierson) (03/22/89)

In article <8903152108.AA06589@zooks.ads.com>, rar@ZOOKS (Bob Riemenschneider) writes:
>There are exceptions, however.  Based on your latest posting, I take it
>you believe "(apply (read) (read))" to be a specially concocted example,
>intended to make your claim sound dubious.  It wasn't; it was a (simplified) 
>example taken from an actual Lisp application.  (The program supports
>interactive multi-attribute utility analysis.  Rather than having the 
>user supply weights used in a linear combination of utilities across
>attributes, the user is asked for an arbitrary computable function from
>[0,1]^number-of-attributes to [0,1] to be used for combination.  The
>designer (me) has arguments that, for many applications, non-linearity
>is required.)  When time for considering translation to another language
>came around, "(apply (read) (read))"--which, when expanded out to include the
>syntactic analysis of the sexpr read in, etc., made up a goodly chunk of
>the program--was the only really hard part.  Writing a simple Lisp-interpreter
>equivalent was evidently necessary, as you observed.  I asked about
>"(apply (read) (read))" because I wanted to know whether either of the
>AdaLISP submissions you received contained at least a simple interpreter
>of the sort you sketch in your posting.  I still want to know.

My only complaint with this is the assumtion that a Common Lisp
_interpreter_ is the correct (or only solution).  It seems likely that
the computable functions mentioned above would be reused several times
in an analysis session.  Therefore they should run as quickly as
possible and the user should have a way to list the previously entered
functions and reselect one.  This means that "(apply (read) (read))"
might be better expressed as:

    (let* ((form (read))
           (fast (compile nil form)))
      (save-form form fast)
      (apply fast (read)))

Doing this in Ada would require implementing a complete Common Lisp
incremental compiler.  Of course, you could do that, but it hardly
seems worth the effort.

Of course, the functions in the actual application described may be
small enough that the overhead of incremental compilation is greater
than the overhead of interpreting the function.  There are
applications in which incremental compilation is nearly vital, there
are others in which it merely wastes resouces, and there are some in
which is makes sense for the program to initially save the interpreted
form and compile it when and if its usage pattern indicates that
compilation would result in a net savings.
-- 
                                            dan

In real life: Dan Pierson, Encore Computer Corporation, Research
UUCP: {talcott,linus,necis,decvax}!encore!pierson
Internet: pierson@encore.com