The Revised Maclisp ManualThe PitmanualPage C-3
Published by HyperMeta Inc.
 
Prev | Index | Next
Common Lisp Conversion
CL Conversion
Trivial Changes
Easy Changes
Hard Changes
Substandard Code
Cosmetic Changes
User-Defined Functions
Non-Portable Code
Donate

Conv: Easy Changes

[Blue Marble]
Climate Change
It's coming
sooner than expected.

The changes in this section can sometimes be done via a careful Tags Query Replace, but may sometimes require more complicated edits. Using Tags Search accompanied by fairly mindless editing (and maybe some creative keyboard macros) will often do the trick as easily.

Common Lisp does not guarantee that (APPEND x NIL) will make a copy of the list x. It also does not guarantee that (SUBST NIL NIL x) will make a full copy of the tree x. These idioms were common in Maclisp/Zetalisp for copying structures. Since the inputs to APPEND and SUBST in Common Lisp are allowed to share structure with their results, the functions COPY-LIST and COPY-TREE should be employed when copying is desired.

    (APPEND list NIL)         becomes  (COPY-LIST list)
    (APPEND list1 list2 NIL)  becomes  (COPY-LIST (APPEND list1 list2))
    . . . etc.
    (APPEND list '())         becomes  (COPY-LIST list)
    . . . etc.
    (APPEND list ())          becomes  (COPY-LIST list)
    . . . etc.
    (SUBST NIL NIL form)      becomes  (COPY-TREE tree)
    (SUBST '() '() form)      becomes  (COPY-TREE tree)
    (SUBST () () form)        becomes  (COPY-TREE tree)
    . . . etc.

The function ARRAYCALL does not exist in Common Lisp. AREF is the intended replacement.

   (ARRAYCALL T array i1 i2 ...)        becomes    (AREF array i1 i2 ...)
   (ARRAYCALL NIL array i1 i2 ...)      becomes    (AREF array i1 i2 ...)
   (ARRAYCALL FIXNUM array i1 i2 ...)   becomes    (THE FIXNUM (AREF array i1 i2 ...))
   (ARRAYCALL FLONUM array i1 i2 ...)   becomes    (THE FLOAT (AREF array i1 i2 ...))

Note well that the special form THE is not valid as a first argument to SETF in portable Common Lisp. The importance of this is in situations such as:

    (DEFMACRO FOO (I) `(ARRAYCALL T *FOO* ,I))

    (SETF (FOO I) ...)

Probably due to an oversight in the design, it is valid to say (SETF (AREF ...) ...) in Common Lisp, but not to say (SETF (THE FIXNUM (AREF ...)) ...). As a result, care should be used when rewriting ARRAYCALL expressions that occur in macro positions to avoid this sort of problem.

The function ASET does not exist in Common Lisp. SETF of an AREF reference is preferred. In the case of ASET being applied, using SETF of APPLY of AREF is explicitly authorized by CLtL.

    (ASET v array i1 i2 ...)       becomes  (SETF (AREF array i1 i2 ...) v)
    (APPLY #'ASET v a i1 i2 ... l) becomes  (SETF (APPLY #'AREF a i1 i2 ... l) v)
    (SI:%LEXPR-ASET v array l)     becomes  (SETF (APPLY #'AREF array l) v)

The Common Lisp function ERROR does essentially the same as the Zetalisp function FERROR. It does not, however, allow an optional NIL to precede the FORMAT string. Also, it does not signal an error of flavor ZL:SYS:FERROR, so code that cares about handling calls to FERROR may have to be looked at more carefully, but in general the following simple rewrites should suffice:

    (FERROR NIL string arg1 arg2 ...)  becomes  (ERROR string arg1 arg2 ...)
    (FERROR string arg1 arg2 ...)      becomes  (ERROR string arg1 arg2 ...)

The names for the accessors for attributes of a symbol are named differently in Common Lisp.

    SYMEVAL           becomes  SYMBOL-VALUE
    FSYMEVAL          becomes  SYMBOL-FUNCTION
    (FSET sym fn)     becomes  (SETF (SYMBOL-VALUE sym) fn)
    GET-PNAME         becomes  SYMBOL-NAME
    PLIST             becomes  SYMBOL-PLIST
    (SETPLIST sym pl) becomes  (SETF (SYMBOL-PLIST sym) pl)

In Maclisp/Zetalisp, PLIST and SETPLIST were defined on lists as well as symbols. In that case, they would use the cdr of the list as its plist. In Common Lisp, SYMBOL-PLIST is not defined to have this behavior, so CDR should be used explicitly. Likewise, the Common Lisp GET operation is only defined on symbols. For non-symbols, GETF is used on a generalized variable reference (a la SETF). The PUTPROP operation does not exist; instead, SETF of a GET or GETF reference is used.

    (GET sym ind)           does not change
    (PUTPROP sym val ind)   becomes  (SETF (GET sym ind) val)
    (GET list ind)          becomes  (GETF list ind)
    (PUTPROP list val ind)  becomes  (SETF (GET list ind) val)

In the case of the PUTPROP rewrite, be careful that you are not depending on order of evaluation effects since the rewrite changes the order of evaluation of val and ind.

The Common Lisp function BREAK enters the debugger while the Zetalisp BREAK function entered a simple READ-EVAL-PRINT loop. Their argument conventions are different, too. In Common Lisp, BREAK evaluates all of its arguments and they are passed on to FORMAT.

    (BREAK msg flag)    becomes>    (IF flag (BREAK "~A" msg))

Common Lisp has no COMMENT special form. If you need one, it's simple to write:

    (DEFMACRO COMMENT (&REST WHATEVER)
      WHATEVER ;ignored
      ''COMMENT)

The Maclisp function SIGNP can be rewritten using a combination of NUMBERP and PLUSP, MINUSP, and ZEROP.

  (SIGNP L x)   becomes  (AND (NUMBERP x) (MINUSP X))
  (SIGNP LE x)  becomes  (AND (NUMBERP x) (NOT (PLUSP X))
  (SIGNP E x)   becomes  (AND (NUMBERP x) (ZEROP X))
  (SIGNP N x)   becomes  (AND (NUMBERP x) (NOT (ZEROP X)))
  (SIGNP GE x)  becomes  (AND (NUMBERP x) (NOT (MINUSP X)))
  (SIGNP G x)   becomes  (AND (NUMBERP x) (PLUSP X))

The functions CASEQ and SELECTQ should be rewritten as calls to CASE. Care must be taken to rewrite any T clause in either of these to an OTHERWISE clause.

The function DFLOAT is not available in Common Lisp, but the Common Lisp FLOAT primitive has been extended to offer equivalent functionality.

    (DFLOAT x)  becomes  (FLOAT x 1.0d0)

The function SORTCAR is not available in Common Lisp, but SORT has been appropriately extended to make up for the lack in functionality.

    (SORTCAR list fn)  becomes  (SORT list fn :KEY #'CAR)

The Maclisp compatibility functions HAULONG and HAIPART can be defined as follows:

    (PROCLAIM '(INLINE HAULONG)) ;optional proclamation
    (DEFUN HAULONG (ARG)
      (INTEGER-LENGTH (ABS ARG)))

    (DEFUN HAIPART (X N)
      (SETQ X (ABS X))
      (IF (MINUSP N) 
          (LOGAND X (- (ASH 1 (- N)) 1))
          (ASH X (MIN (- N (HAULONG X)) 0))))

Common Lisp has replaced *CATCH and *THROW by new operators CATCH and THROW. There are differences in the value-passing conventions between the two pairs of operators. See the documentation for details. The following compatibility definitions for *CATCH and *THROW should suffice for most applications:

 (DEFMACRO *CATCH (TAG &BODY FORMS)
   (LET ((V (GENTEMP)))
     (COND ((OR (ATOM TAG) (EQ (CAR TAG) 'QUOTE))
            `(BLOCK ,V
               (LET ((,V (CATCH ,TAG (RETURN-FROM ,V (VALUES (PROGN ,@FORMS))))))
                 (RETURN-FROM ,V (VALUES ,V ,TAG)))))
           (T
            `(LET ((,V ,TAG))
               (*CATCH ,V ,@FORMS))))))

  (PROCLAIM '(INLINE *THROW)) ;optional proclamation
  (DEFSUBST *THROW (TAG FORM)
    (THROW TAG (VALUES FORM)))

The utility functions FIRSTN and RASSQ are not provided in Common Lisp. They are, however, simple to define:

  (DEFUN FIRSTN (N LIST)
    (DO ((I 0 (+ I 1))
         (R '() (CONS (CAR L) R))
         (L LIST (CDR L)))
        ((OR (>= I N) (NULL L)) (NREVERSE R))))

  (DEFUN RASSQ (X Y)
    (DO ((L Y (CDR L)))
        ((NULL L) NIL)
      (IF (EQ (CDAR L) X) (RETURN (CAR L)))))

The Lisp 1.5 functions SASSOC and SASSQ have no name in Common Lisp, but can be simulated easily:

    (SASSOC key alist fn)    becomes    (OR (ASSOC key alist :TEST #'EQUAL) (FUNCALL fn))
    (SASSQ key alist fn)     becomes    (OR (ASSOC key alist :TEST #'EQ) (FUNCALL fn))

CL Conversion (1 2 (3) 4 5 6 7 8)


The Revised Maclisp Manual (Sunday Morning Edition)
Published Sunday, December 16, 2007 06:17am EST, and updated Sunday, July 6, 2008.
Prev | Index | Next