From: Ian "Wildebeest" Flanigan
Subject: Problems compiling PCL with AKCL-1-470
Date: 
Message-ID: <1990Apr6.171346.7356@cec1.wustl.edu>
Hello!

Has anyone tried to compile PCL with AKCL 1.470?  I have tried, but
according to the PCL documentation I need to modify the "turbo-closure"
routine.  The problems began when I made the changes to AKCL that PCL
requires: adding the two if statements at the end of the routine.  These
two if statements, however, use cc.cc_start and cc.cc_size, neither of
which is defined, so the compiler chokes and dies when it tries to compile
them.  The real problem is that part of PCL makes extensive use of these
parts of the cclosure structure.  So, does anyone know a soultion?  Is
there some bit that the docs for PCL don't mention?

Thanks a bunch.


Ian Flanigan

····@ai.wustl.edu              "You can never have too many napkins."
·······················@uucp

From: Toshimi sawada
Subject: Re: Problems compiling PCL with AKCL-1-470
Date: 
Message-ID: <41669@etlcom.etl.go.jp>
[····@ai.wustl.edu in <····················@cec1.wustl.edu>]:
 |Hello!
 |
 |Has anyone tried to compile PCL with AKCL 1.470?  I have tried, but
 |according to the PCL documentation I need to modify the "turbo-closure"
 |routine.  The problems began when I made the changes to AKCL that PCL
 |requires: adding the two if statements at the end of the routine.  These
 |two if statements, however, use cc.cc_start and cc.cc_size, neither of
 |which is defined, so the compiler chokes and dies when it tries to compile
 |them.  The real problem is that part of PCL makes extensive use of these
 |parts of the cclosure structure.  So, does anyone know a soultion?  Is
 |there some bit that the docs for PCL don't mention?

I've successed compiling  PCL (victoria version), with AKCL 1.465.
(I hope my solution could be also applied to verion 1.470 or later).

Your main problem is that AKCL changes internal data structure of KCl.

But you can  compile PCL without changing AKCL by apropreate patch
file and low.lisp for AKCL.

Here are my akcl-patch.lisp and akcl-low.lisp modefied
from (pure)KCL version. 

Try them please. If you have any questions or problems, please inform me.

--
Toshimi Sawada(*)
Computer Language Section, Electrotechnical Laboratory (ETL)
1-1-4 Umezono, Tsukuba, Ibaraki 305, JAPAN
TEL: +81 298 58 5890
E-Mail: ······@etl.go.jp
--
(*)SoftwareResearch Associates, Inc., 1-1-1
   Hirakawacho, Chiyoda, Tokyo; on leave at Electrotechnical
   Laboratory. 

-------------------(cut here)-----------------------------------------------
# This is a shell archive.  Remove anything before this line,
# then unpack it by saving it in a file and typing "sh file".
#
# Wrapped by  on Mon Apr  9 15:29:33 JST 1990
# Contents:  defsys-changes.text akcl-patches.lsp akcl-low.lsp
 
echo x - defsys-changes.text
sed ····@//' > "defsys-changes.text" <<·@//E*O*F defsys-changes.text//'
CHANGES IN "defsys.lisp"

AKCL contains both kcl and akcl in *features*, 
we must distinguish akcl from (pure) kcl in our akcl version of pcl.

(1) change *port* like...
(defvar *port*
        '(            :
		      :
          #+(and kcl (not  AKCL))KCL
	  #+AKCL	         AKCL
                      :
          #+:coral               coral))

(2) and *pcl-directory* 
(defvar *pcl-directory*
                       :
  #+(and KCL (not AKCL))     (pathname "/usr/pcl/")
  #+AKCL		     (pathname "/usr/users/sawada/CAFE/dist/pcl/")
                       :
  )

(3) finally, system definition of pcl:
(defsystem pcl
	   *pcl-directory*
  ;; file         load           compile           files which      port
  ;;              environment    environment       force the of
  ;;                                               recompilation
  ;;                                               of this file
  ((rel-6-patches t              t                ()                rel-6)
   (kcl-patches   t              t                ()                kcl)
                       :
   ;; add enty for akcl-patches 
   (akcl-patches  t              t                ()                akcl)
                       :   

   (kcl-low      (low)           (low)            (low)            KCL)
   ;; and low for akcl
   (akcl-low     (low)           (low)            (low)            AKCL)
                       :   
   (7debug        t              t                ()               rel-7)
   ))
@//E*O*F defsys-changes.text//
chmod u=rw,g=rw,o=r defsys-changes.text
 
echo x - akcl-patches.lsp
sed ····@//' > "akcl-patches.lsp" <<·@//E*O*F akcl-patches.lsp//'
;;;-*-Mode:LISP; Package:(PCL LISP 1000); Base:10; Syntax:Common-lisp -*-
;;;
;;; *************************************************************************
;;; Copyright (c) 1985, 1986, 1987, 1988 Xerox Corporation.
;;; All rights reserved.
;;;
;;; Use and copying of this software and preparation of derivative works
;;; based upon this software are permitted.  Any distribution of this
;;; software or derivative works must comply with all applicable United
;;; States export control laws.
;;; 
;;; This software is made available AS IS, and Xerox Corporation makes no
;;; warranty about the software, its performance or its conformity to any
;;; specification.
;;; 
;;; Any person obtaining a copy of this software is requested to send their
;;; name and post office or electronic mail address to:
;;;   CommonLoops Coordinator
;;;   Xerox PARC
;;;   3333 Coyote Hill Rd.
;;;   Palo Alto, CA 94304
;;; (or send Arpanet mail to ··························@Xerox.arpa)
;;;
;;; Suggestions, comments and requests for improvements are also welcome.
;;; *************************************************************************
;;;

(in-package 'system)
(eval-when (compile eval load)
	   (setq compiler::*compile-ordinaries* t)
	   (push :turbo-closure *features*))

(eval-when (compile) (proclaim '(optimize (safety 2) (space 3))))

;;;
;;; setf patches
;;;

(defun get-setf-method (form)
  (multiple-value-bind (vars vals stores store-form access-form)
      (get-setf-method-multiple-value form)
    (unless (listp vars)
	    (error 
 "The temporary variables component, ~s, 
  of the setf-method for ~s is not a list."
             vars form))
    (unless (listp vals)
	    (error 
 "The values forms component, ~s, 
  of the setf-method for ~s is not a list."
             vals form))
    (unless (listp stores)
	    (error 
 "The store variables component, ~s,  
  of the setf-method for ~s is not a list."
             stores form))
    (unless (= (list-length stores) 1)
	    (error "Multiple store-variables are not allowed."))
    (values vars vals stores store-form access-form)))

(defun get-setf-method-multiple-value (form &aux tem)
  (cond ((symbolp form)
	 (let ((store (gensym)))
	   (values nil nil (list store) `(setq ,form ,store) form)))
	((or (not (consp form)) (not (symbolp (car form))))
	 (error "Cannot get the setf-method of ~S." form))
	((get (car form) 'setf-method)
	 (apply (get (car form) 'setf-method) (cdr form)))
	((or (get (car form) 'setf-update-fn)
	     (setq tem (get (car form) 'si::structure-access)))
	 (let ((vars (mapcar #'(lambda (x)
	                         (declare (ignore x))
	                         (gensym))
	                     (cdr form)))
	       (store (gensym)))
	   (values vars (cdr form) (list store)
		   (cond (tem
			  (setf-structure-access (car vars) (car tem)
						 (cdr tem) store))
			 (t
			  `(,(get (car form) 'setf-update-fn)
			    ,@vars ,store)))
		   (cons (car form) vars))))
	((get (car form) 'setf-lambda)
	 (let* ((vars (mapcar #'(lambda (x)
	                          (declare (ignore x))
	                          (gensym))
	                      (cdr form)))
		(store (gensym))
		(l (get (car form) 'setf-lambda))
		(f `(lambda ,(car l) 
		      (funcall #'(lambda ,(cadr l) ,@(cddr l))
			       ',store))))
	   (values vars (cdr form) (list store)
		   (apply f vars)
		   (cons (car form) vars))))
	((macro-function (car form))
	 (get-setf-method-multiple-value (macroexpand-1 form)))
	(t
	 (error "Cannot expand the SETF form ~S." form))))
@//E*O*F akcl-patches.lsp//
chmod u=rw,g=rw,o=r akcl-patches.lsp
 
echo x - akcl-low.lsp
sed ····@//' > "akcl-low.lsp" <<·@//E*O*F akcl-low.lsp//'
;;;-*-Mode:LISP; Package:(PCL Lisp 1000); Base:10; Syntax:Common-lisp -*-
;;;
;;; *************************************************************************
;;; Copyright (c) 1985, 1986, 1987 Xerox Corporation.  All rights reserved.
;;;
;;; Use and copying of this software and preparation of derivative works
;;; based upon this software are permitted.  Any distribution of this
;;; software or derivative works must comply with all applicable United
;;; States export control laws.
;;; 
;;; This software is made available AS IS, and Xerox Corporation makes no
;;; warranty about the software, its performance or its conformity to any
;;; specification.
;;; 
;;; Any person obtaining a copy of this software is requested to send their
;;; name and post office or electronic mail address to:
;;;   CommonLoops Coordinator
;;;   Xerox PARC
;;;   3333 Coyote Hill Rd.
;;;   Palo Alto, CA 94304
;;; (or send Arpanet mail to ··························@Xerox.arpa)
;;;
;;; Suggestions, comments and requests for improvements are also welcome.
;;; *************************************************************************
;;;
;;; The version of low for Kyoto Common Lisp (KCL)
(in-package 'pcl)

;;;
;;; The reason these are here is because the KCL compiler does not allow
;;; LET to return FIXNUM values as values of (c) type int, hence the use
;;; of LOCALLY (which expands into (LET () (DECLARE ...) ...)) forces
;;; conversion of ints to objects.
;;; 
(defmacro %logand (&rest args)
  (reduce-variadic-to-binary 'logand args 0 t 'fixnum))

(defmacro %logxor (&rest args)
  (reduce-variadic-to-binary 'logxor args 0 t 'fixnum))

(defmacro %+ (&rest args)
  (reduce-variadic-to-binary '+ args 0 t 'fixnum))

(defmacro %- (x y)
  `(the fixnum (- (the fixnum ,x) (the fixnum ,y))))

(defmacro %* (&rest args)
  (reduce-variadic-to-binary '* args 1 t 'fixnum))

(defmacro %/ (x y)
  `(the fixnum (/ (the fixnum ,x) (the fixnum ,y))))

(defmacro %1+ (x)
  `(the fixnum (1+ (the fixnum ,x))))

(defmacro %1- (x)
  `(the fixnum (1- (the fixnum ,x))))

(defmacro %svref (vector index)
  `(svref (the simple-vector ,vector) (the fixnum ,index)))

(defsetf %svref (vector index) (new-value)
  `(setf (svref (the simple-vector ,vector) (the fixnum ,index))
         ,new-value))


;;;
;;; iwmc-class-p
;;;
(si:define-compiler-macro iwmc-class-p (x)
  (once-only (x)
    `(and (si:structurep ,x)
	  (eq (si:structure-name ,x) 'iwmc-class))))
#|
(CLines
 "object Str_Name (obj)"
 "object obj;"
 "{"
 "struct s_data {object name;
	       int length;
	       object raw;
	       object included;
	       object includes;
	       object staticp;
	       object print_function;
	       object slot_descriptions;
	       object slot_position;
	       int    size;
	       object has_holes;
	     };

#define S_DATA(x) ((struct s_data *)((x)->str.str_self))
"
 "return(S_DATA(obj->str.str_def)->name);"
 "}"
 )

(defentry  str_name_aux (object) (object "Str_Name"))
|#

(dolist (inline '((si:structurep
		    ((t) compiler::boolean nil nil "type_of(#0)==t_structure")
		    compiler::inline-always)
		  ;;(si:structure-name
		  ;;((t) t nil nil "Str_Name(#0)")
		  ;;compiler::inline-unsafe)
		  ))
  (setf (get (first inline) (third inline)) (list (second inline))))

(setf (get 'cclosure-env 'compiler::inline-always)
      (list '((t) t nil nil "(#0)->cc.cc_env")))

;;;
;;; turbo-closure patch.  See the file kcl-mods.text for details.
;;;
#+:turbo-closure
(progn
(CLines
  "object tc_cc_env_nthcdr (n,tc)"
  "object n,tc;                        "
  "{return (type_of(tc)==t_cclosure&&  "
  "         tc->cc.cc_turbo!=NULL&&    "

  "         type_of(n)==t_fixnum)?     "
  "         tc->cc.cc_turbo[fix(n)]:   " ; assume that n is in bounds
  "         Cnil;                      "
  "}                                   "
  )

(defentry tc-cclosure-env-nthcdr (object object) (object tc_cc_env_nthcdr))

(setf (get 'tc-cclosure-env-nthcdr 'compiler::inline-unsafe)
      '(((fixnum t) t nil nil "(#1)->cc.cc_turbo[#0]")))
)


;;;; low level stuff to hack compiled functions and compiled closures.
;;;
;;; The primary client for this is fsc-low, but since we make some use of
;;; it here (e.g. to implement set-function-name-1) it all appears here.
;;;

(eval-when (compile eval)

(defmacro define-cstruct-accessor (accessor structure-type field value-type
					    field-type tag-name)
  (let ((setf (intern (concatenate 'string "SET-" (string accessor))))
	(caccessor (format nil "pcl_get_~A_~A" structure-type field))
	(csetf     (format nil "pcl_set_~A_~A" structure-type field))
	(vtype (intern (string-upcase value-type))))
    `(progn
       (CLines ,(format nil "~A ~A(~A)                ~%~
                             object ~A;               ~%~
                             { return ((~A) ~A->~A.~A); }       ~%~
                                                      ~%~
                             ~A ~A(~A, new)           ~%~
                             object ~A;               ~%~
                             ~A new;                  ~%~
                             { return ((~A)(~A->~A.~A = ~Anew)); } ~%~
                            "
			value-type caccessor structure-type 
			structure-type
			value-type structure-type tag-name field
			value-type csetf structure-type
			structure-type 
			value-type 
			value-type structure-type tag-name field field-type
			))

       (defentry ,accessor (object) (,vtype ,caccessor))
       (defentry ,setf (object ,vtype) (,vtype ,csetf))


       (defsetf ,accessor ,setf)

       )))
)
;;; 
;;; struct cfun {			/*  compiled function header  */
;;;		FIRSTWORD;
;;;	object	cf_name;	/*  compiled function name  */
;;;	int	(*cf_self)();	/*  entry address  */
;;;	object	cf_data;	/*  data the function uses  */
;;;				/*  for GBC  */
;;; };
;;; struct cfdata {
;;;     FIRSTWORD;
;;;     char *cfd_start;             /* beginning of contblock for fun */
;;;     int cfd_size;              /* size of contblock */
;;;     int cfd_fillp;             /* size of self */
;;;     object *cfd_self;          /* body */
;;;   };

(define-cstruct-accessor cfun-name  "cfun" "cf_name"  "object" "(object)" "cf")
(define-cstruct-accessor cfun-self  "cfun" "cf_self"  "int" "(int (*)())" 
                         "cf")
(define-cstruct-accessor cfun-data  "cfun" "cf_data"  "object" "(object)" "cf")
;(define-cstruct-accessor cfun-start "cfun" "cf_start" "int" "(char *)" "cf")
;(define-cstruct-accessor cfun-size  "cfun" "cf_size"  "int" "(int)" "cf")
(CLines
  "object pcl_cfunp (x)              "
  "object x;                         "
  "{if(x->c.t == (int) t_cfun)       "
  "  return (Ct);                    "

  "  else                            "
  "    return (Cnil);                "
  "  }                               "
  )

(defentry cfunp (object) (object pcl_cfunp))

;;; 
;;;  struct cclosure {
;;;		FIRSTWORD;
;;;
;;;	object	cc_name;
;;;	int	(*cc_self)();
;;;	object	cc_env;
;;;	object	cc_data;
;;;	object	*cc_turbo;
;;; };
;;; struct cfdata {
;;;     FIRSTWORD;
;;;     char *cfd_start;             /* beginning of contblock for fun */
;;;     int cfd_size;              /* size of contblock */
;;;     int cfd_fillp;             /* size of self */
;;;     object *cfd_self;          /* body */
;;;   };
(define-cstruct-accessor cclosure-name "cclosure"  "cc_name"  "object"
                         "(object)" "cc")          
(define-cstruct-accessor cclosure-self "cclosure"  "cc_self"  "int" 
                         "(int (*)())" "cc")
(define-cstruct-accessor cclosure-data "cclosure"  "cc_data"  "object"
                          "(object)" "cc")
;(define-cstruct-accessor cclosure-start "cclosure" "cc_start" "int" 
;                         "(char *)" "cc")
;(define-cstruct-accessor cclosure-size "cclosure"  "cc_size"  "int"
;			 "(int)" "cc")
(define-cstruct-accessor cclosure-env "cclosure"   "cc_env"   "object"
                         "(object)" "cc")


(CLines
  "object pcl_cclosurep (x)          "
  "object x;                         "
  "{if(x->c.t == (int) t_cclosure)   "
  "  return (Ct);                    "
  "  else                            "
  "   return (Cnil);                 "
  "  }                               "
  )

(defentry cclosurep (object) (object pcl_cclosurep))

(progn
  (CLines
   " struct cfdata {
     FIRSTWORD;
     char *cfd_start;             /* beginning of contblock for fun */
     int cfd_size;              /* size of contblock */
     int cfd_fillp;             /* size of self */
     object *cfd_self;          /* body */
   };
#define CF_DATA(x) ((struct cfdata *)((x)->cf.cf_data))
#define CC_DATA(x) ((struct cfdata *)((x)->cc.cc_data))
"
"int pcl_get_cfun_cf_start (cfun)
object cfun;
{return ((int)(CF_DATA(cfun)->cfd_start));}
"
"int pcl_set_cfun_cf_start (cfun, new)
object cfun;
int new;
{ return ((int)(CF_DATA(cfun)->cfd_start = (char *) new));}
"
"int pcl_get_cfun_cf_size (cfun)
object cfun;
{return ((int)(CF_DATA(cfun)->cfd_size));}
"
"int pcl_set_cfun_cf_size(cfun, new)
object cfun;
int new;
{ return ((int)(CF_DATA(cfun)->cfd_start =  new));}
"
"int pcl_get_cclosure_cc_start (cc)
object cc;
{return ((int)(CC_DATA(cc)->cfd_start));}
"
"int pcl_set_cclosure_cc_start (cc, new)
object cc;
int new;
{ return ((int) (CC_DATA(cc)->cfd_start = (char *) new));}
"
"int pcl_get_cclosure_cc_size (cc)
object cc;
{return ((int) (CC_DATA(cc)->cfd_size));}
"
"int pcl_set_cclosure_cc_size (cc, new)
object cc;
int new;
{ return ((int) (CC_DATA(cc)->cfd_size = new));}
"
)
  (defentry cfun-start (object) (int "pcl_get_cfun_cf_start"))
  (defentry set-cfun-start (object int) (int "pcl_set_cfun_cf_start"))
  (defsetf cfun-start set-cfun-start)
  (defentry cfun-size (object) (int "pcl_get_cfun_cf_size"))
  (defentry set-cfun-size (object int) (int "pcl_set_cfun_cf_size"))
  (defsetf cfun-size set-cfun-size)
  (defentry cclosure-start (object) (int "pcl_get_cclosure_cc_start"))
  (defentry set-cclosure-start (object int) (int "pcl_set_cclosure_cc_start"))
  (defsetf cclosure-start set-cclosure-start)
  (defentry cclosure-size (object) (int "pcl_get_cclosure_cc_size"))
  (defentry set-cclosure-size (object int) (int "pcl_set_cclosure_cc_size"))
  (defsetf cclosure-size set-cclosure-size)
)
  ;;   
;;;;;; Load Time Eval
  ;;
;;; 

;;; This doesn't work because it looks at a global variable to see if it is
;;; in the compiler rather than looking at the macroexpansion environment.
;;; 
;;; The result is that if in the process of compiling a file, we evaluate a
;;; form that has a call to load-time-eval, we will get faked into thinking
;;; that we are compiling that form.
;;;
;;; THIS NEEDS TO BE DONE RIGHT!!!
;;; 
;(defmacro load-time-eval (form)
;  ;; In KCL there is no compile-to-core case.  For things that we are 
;  ;; "compiling to core" we just expand the same way as if were are
;  ;; compiling a file since the form will be evaluated in just a little
;  ;; bit when gazonk.o is loaded.
;  (if (and (boundp 'compiler::*compiler-input*)  ;Hack to see of we are
;	   compiler::*compiler-input*)		  ;in the compiler!
;      `'(si:|#,| . ,form)
;      `(progn ,form)))

(defmacro load-time-eval (form)
  (read-from-string (format nil "'#,~S" form)))

(defmacro memory-block-ref (block offset)
  `(svref (the simple-vector ,block) (the fixnum ,offset)))

  ;;   
;;;;;; Generating CACHE numbers
  ;;
;;; This needs more work to be sure it is going as fast as possible.
;;;   -  The calls to si:address should be open-coded.
;;;   -  The logand should be open coded.
;;;   

;(defmacro symbol-cache-no (symbol mask)
;  (if (and (constantp symbol)
;	   (constantp mask))
;      `(load-time-eval (logand (ash (si:address ,symbol) -2) ,mask))
;      `(logand (ash (the fixnum (si:address ,symbol)) -2) ,mask)))

(defmacro object-cache-no (object mask)
  `(logand (the fixnum (si:address ,object)) ,mask))

  ;;   
;;;;;; printing-random-thing-internal
  ;;
(defun printing-random-thing-internal (thing stream)
  (format stream "~O" (si:address thing)))


(defun set-function-name-1 (fn new-name ignore)
  (cond ((cclosurep fn)
	 (setf (cclosure-name fn) new-name))
	((cfunp fn)
	 (setf (cfun-name fn) new-name))
	((and (listp fn)
	      (eq (car fn) 'lambda-block))
	 (setf (cadr fn) new-name))
	((and (listp fn)
	      (eq (car fn) 'lambda))
	 (setf (car fn) 'lambda-block
	       (cdr fn) (cons new-name (cdr fn)))))
  fn)




#|
(defconstant most-positive-small-fixnum 1024)  /* should be supplied */
(defconstant most-negative-small-fixnum -1024) /* by ibuki */

(defmacro symbol-cache-no (symbol mask)
  (if (constantp mask)
      (if (and (> mask 0)
	       (< mask most-positive-small-fixnum))
	  (if (constantp symbol)
	      `(load-time-eval (coffset ,symbol ,mask 2))
	    `(coffset ,symbol ,mask 2))
	(if (constantp symbol)
	    `(load-time-eval 
	       (logand (ash (the fixnum (si:address ,symbol)) -2) ,mask))
	  `(logand (ash (the fixnum (si:address ,symbol)) -2) ,mask)))
    `(logand (ash (the fixnum (si:address ,symbol)) -2) ,mask)))


(defmacro object-cache-no (object mask)
  (if (and (constantp mask)
	   (> mask 0)
	   (< mask most-positive-small-fixnum))
      `(coffset ,object ,mask 4)
    `(logand (ash (the fixnum (si:address ,object)) -4) ,mask)))

(CLines
  "object pcl_coffset (sym,mask,lshift)"
  "object sym,mask,lshift;"
  "{"
  "	return(small_fixnum(((int)sym >> fix(lshift)) & fix(mask)));"
  "}"
  )

(defentry coffset (object object object) (object pcl_coffset))


|#
@//E*O*F akcl-low.lsp//
chmod u=rw,g=rw,o=r akcl-low.lsp
 
exit 0
From: Jeff Dalton
Subject: Re: Problems compiling PCL with AKCL-1-470
Date: 
Message-ID: <2188@skye.ed.ac.uk>
In article <·····@etlcom.etl.go.jp> ······@etl.go.jp writes:
>I've successed compiling  PCL (victoria version), with AKCL 1.465.
>(I hope my solution could be also applied to verion 1.470 or later).

Is it really this hard?  I compiled Victoria Day PCL in akcl 1.122
without any special effort at all.
From: Toshimi sawada
Subject: Re: Problems compiling PCL with AKCL-1-470
Date: 
Message-ID: <41819@etlcom.etl.go.jp>
[····@aiai.ed.ac.uk in <····@skye.ed.ac.uk>]:
 |
 |In article <·····@etlcom.etl.go.jp> ······@etl.go.jp writes:
 |>I've successed compiling  PCL (victoria version), with AKCL 1.465.
 |>(I hope my solution could be also applied to verion 1.470 or later).
 |
 |Is it really this hard?  I compiled Victoria Day PCL in akcl 1.122
 |without any special effort at all.

I don't know about version 1.122 of AKCL at all, but at least in version
1.465, structure of compiled function and closure are changed from
original (pure) KCl, so kcl-low.lisp of PCL doesn't works well.

Yes, it is not hard ofcourse, only you must do is to examine internal
structure of compiled function and closure of AKCL, and to patch
kcl-low.lisp approprietely.

--
Toshimi Sawada
Computer Language Section, Electrotechnical Laboratory (ETL)
1-1-4 Umezono, Tsukuba, Ibaraki 305, JAPAN
TEL: +81 298 58 5890
E-Mail: ······@etl.go.jp
From: Ian "Wildebeest" Flanigan
Subject: Re: Problems compiling PCL with AKCL-1-470
Date: 
Message-ID: <1990Apr13.004536.16115@cec1.wustl.edu>
In article <·····@etlcom.etl.go.jp> ······@etl.go.jp writes:
>
>I've successed compiling  PCL (victoria version), with AKCL 1.465.
>(I hope my solution could be also applied to verion 1.470 or later).
> :
> :
>Here are my akcl-patch.lisp and akcl-low.lisp modefied
>from (pure)KCL version. 
>
>Try them please. If you have any questions or problems, please inform me.
>

The fixes work quite well . . . to a point.  After making the changes, PCL
compiled right up to the fixup.lisp file where is produces the following:

Finished compiling /local/cics/src/pcl/dfun.o.
Loading binary of DFUN...
Compiling FIXUP...
Compiling /local/cics/src/pcl/fixup.lisp.
Error: LAMBDA-CLOSURE is not a function.
Error signalled by an anonymous function.
Backtrace:  > eval > fix-early-generic-functions > lambda-closure > prog >
return > funcall > |(METHOD COMPUTE-APPLICABLE-METHODS-USING-CLASSES
(GENERIC-FUNCTION T))| > remove-if-not > lambda-closure > prog > return >
funcall > lambda-closure > prog > return > funcall > |(METHOD
COMPUTE-APPLICABLE-METHODS-USING-CLASSES (GENERIC-FUNCTION T))| >
remove-if-not > lambda-closure > prog > return > funcall > lambda-closure
> prog > return > funcall > |(METHOD
COMPUTE-APPLICABLE-METHODS-USING-CLASSES (GENERIC-FUNCTION T))| >
remove-if-not > lambda-closure > prog > return > funcall
; (FIX-EARLY-GENERIC-FUNCTIONS) is being compiled.
;;; The form (FIX-EARLY-GENERIC-FUNCTIONS) was not evaluated successfully.
;;; You are recommended to compile again.
No FASL generated.
Loading binary of FIXUP...
Error: Cannot open the file /local/cics/src/pcl/fixup.o.
Error signalled by LOAD.

Broken at LOAD.  Type :H for Help.
>>

I've been wnadering around trying to find something wrong, but not being a
Lisp guru, I haven't been too successful.  If anyone has any tips or
pointers, again, I'd be very greatful.


>--
>Toshimi Sawada(*)
>Computer Language Section, Electrotechnical Laboratory (ETL)
>1-1-4 Umezono, Tsukuba, Ibaraki 305, JAPAN
>TEL: +81 298 58 5890
>E-Mail: ······@etl.go.jp
>--
>(*)SoftwareResearch Associates, Inc., 1-1-1
>   Hirakawacho, Chiyoda, Tokyo; on leave at Electrotechnical
>   Laboratory. 


Ian Flanigan

····@ai.wustl.edu              "You can never have too many napkins."
·······················@uucp
From: Toshimi sawada
Subject: Re: Problems compiling PCL with AKCL-1-470
Date: 
Message-ID: <41887@etlcom.etl.go.jp>
[····@ai.wustl.edu in <······················@cec1.wustl.edu>]:

 |The fixes work quite well . . . to a point.  After making the changes, PCL
 |compiled right up to the fixup.lisp file where is produces the following:
 |
 |Finished compiling /local/cics/src/pcl/dfun.o.
 |Loading binary of DFUN...
 |Loading binary of DFUN...
 |Compiling FIXUP...
 |Compiling /local/cics/src/pcl/fixup.lisp.
 |Error: LAMBDA-CLOSURE is not a function.
 |Error signalled by an anonymous function.

Sorry, Ian, my fixes are for version "5/22/89 Victoria Day PCL".
I have not tired to apply them to any other version of PCL.
Is "Victoria Day" too old for you?
(I never heard "dfun.lisp").
--
Toshimi Sawada
Software Reserach Associates Inc.
on leave at Computer Language Section, Electrotechnical Laboratory
1-1-4 Umezono, Tsukuba, Ibaraki 305, JAPAN
TEL: +81 298 58 5890
E-Mail: ······@etl.go.jp