From: Yann Planchais
Subject: problem with my small program
Date: 
Message-ID: <365DF49C.130A4A1@emi.u-bordeaux.fr>
In a project, we must make a function which create a circuit with AND
with an arbitrary number of inputs.

When we create an instance of this circuit, here is the message of the
Lisp language:
---------------------------------------------------------------------
Converted CIRCUITS::AUX.
[GC threshold exceeded with 2,217,536 bytes in use.  Commencing GC.]
[GC completed with 737,360 bytes retained and 1,480,176 bytes freed.]
[GC will next occur when at least 2,737,360 bytes are in use.]

Argument X is not a NUMBER: NIL.

Restarts:
  0: [CONTINUE] Return NIL from load of "demo".
  1: [ABORT   ] Return to Top-Level.

Debug  (type H for help)

(KERNEL:TWO-ARG-+ NIL NIL)
Source: Error finding source: 
Error in function DEBUG::GET-FILE-TOP-LEVEL-FORM:  Source file no longer
exists:
  target:code/numbers.lisp.
-------------------------------------------------------------

Please if you find the solution , mail to us.
Thank you

Hereis the source of the programme:
--------------------------[circuits.lisp]---------------------------
(defpackage "CIRCUITS"
  (:use "COMMON-LISP" "EXTENSIONS")
  (:export "CONNECT" "OUTPUT-STATES" "OUTPUT-STATE"  "SIMULATE"
           "SWITCH" "MAKE-SWITCH" "SWITCH-TOGGLE" "SWITCH-POSITION"
	   "ZERO" "MAKE-ZERO"
	   "COMPLEX-CIRCUIT" "MAKE-COMPLEX-CIRCUIT"
	   "DEF-OUTPUT" "BRANCH-INPUT" "SHORT-CIRCUIT"
	   "MAKE-FLIP-FLOP" "PARALLEL" "SERIE" "MAKE-ADD-ONE-BIT"
	   "MAKE-ADD-N-BIT" 
	   "COMP-DESCRIBE"))
	   
(in-package circuits)


;;;; components with some inputs and outputs

(defclass component ()
  ((inputs :reader component-inputs)
   (outputs :reader component-outputs)
   (nb-in :reader component-nb-in :initarg :nb-in)
   (nb-out :reader component-nb-out :initarg  :nb-out))
  (:documentation "a network component"))


(defmethod initialize-instance :after ((c component) &key)
  (setf (slot-value c 'inputs)
	(make-array (slot-value c 'nb-in)))
  (setf (slot-value c 'outputs)
	(make-array (slot-value c 'nb-out))))


(defgeneric comp-describe ((c component) &key (stream t)))
  
(defun  connect (from n-output to n-input)
  "(connect from i to j) connects the i-th output of component from to
the j-th input of component to"
  (setf (svref (component-inputs to) n-input)
	#'(lambda () 
	    (output-state from n-output)))
  t)


(defun output-states (c)
  "(output-states c) returns the vector of state outputs of c"
  (map 'vector
       #'(lambda (o) (funcall o))
       (component-outputs  c)))


(defun output-state (c position )
  "(output-states c i) returns the i-th  state output of c"
  (funcall (svref (component-outputs c) position)))

;;;; simulation


;;;  realizes the second half of a clock tic
(defmethod update ((c component))
  )

;;;  realizes the first half of a clock tic
(defmethod compute-temp-state ((c component))
					; nothing
  )


(defun simulate (c  time)
  "(simulate <component> <nb-of-tics>)"
  (format t "~s~%" (output-states c))
  (dotimes (i time t)
    (compute-temp-state c)
    (update c)
    (format t "~s~%" (output-states c))))



(defmethod comp-describe ((c component) &key (stream t) )
  (format stream "a plain component with ~d inputs and ~d outputs~%"
	  (component-nb-in c)
	  (component-nb-out c))
  (format stream "bound inputs : ~s~%"
	  (map 'vector #'functionp (component-inputs c)))
  (format stream "bound outputs : ~s~%"
	  (map 'vector #'functionp (component-outputs c))))



;;;; zeros

(defclass zero (component)
  ((nb-in :initform 0)
   (nb-out :initform 1)))


(defmethod initialize-instance :after ((z zero) &key)
  (setf (svref  (component-outputs z) 0) 
	#'(lambda () nil)))

(defun make-zero ()
  (make-instance 'zero))

;;;; switches

(defclass switch (component)
  ((nb-in :initform 0
	  :allocation :class)
   (nb-out :initform 1
	   :allocation :class)
   (switch-position :initform Nil
		    :accessor switch-position)))


(defmethod initialize-instance :after ((sw switch) &key)
  (setf (svref  (component-outputs sw) 0) 
	#'(lambda () (switch-position sw))))

(defun make-switch ()
  (make-instance 'switch))


(defun switch-toggle (sw)
  (setf (switch-position sw)
	(not (switch-position  sw ))))

(defmethod comp-describe ((sw switch) &key (stream t))
  (format stream "a switch at position ~s~%" 
	  (switch-position sw)))



;;;; portes

(defclass gate (component)
  ((nb-out :initform 1 :allocation :class)
   (nb-in :initform 2 ; valeur par defaut
	  :allocation :class)
   (fun :reader gate-fun
	:allocation :class)
   (temp-state)
   (current-state :reader current-state
		  :initform nil))
  (:documentation
   "a component n to 1 together with a function applied to its inputs"))

(defmethod initialize-instance :after ((g gate) &key)
  (setf (svref (slot-value g 'outputs) 0)
	#'(lambda ()             
	    (current-state g))))



(defmethod comp-describe ((g gate) &key (stream t))
  (format stream "a gate with ~d entries and output at : ~d ~%"
	  (component-nb-in g)
	  (output-state g 0)))

(defmethod compute-temp-state ((g gate))
  (setf (slot-value g 'temp-state )
	(apply (gate-fun g)
	       (coerce (map 'vector  #'funcall (component-inputs g))
		       'list))))


(defmethod update ((g gate))
  (setf (slot-value g 'current-state) 
	(slot-value g 'temp-state)))




(defun gate-class (name)
  (intern (concatenate 'string
		       (string-upcase name)
		       "-GATE")))

(defun build-gate (name)
  (intern (concatenate 'string
		       "MAKE-"
		       (string-upcase name)
		       "-GATE")))


(defmacro defgate (name fun &key arity)
  (let ((class-name (gate-class name))
	(maker (build-gate name)))
    `(progn (defclass ,class-name (gate)
	      ((fun :initform (function ,fun)
		    :allocation :class)
	       ,@(when (numberp arity)
		   `((nb-in :initform ,arity
			    :allocation :class)))))
	    (defun ,maker ()
	      (make-instance ',class-name))
	    (export (list ',class-name ',maker))
	    ',class-name)))


;;;; specialized gates

(defgate and (lambda (x y) (and x y)))

(defgate or (lambda (x y) (or x y)))

(defgate xor (lambda (x y) (not (eql x y))))

(defgate nor (lambda (x y) (not (or x y))))

(defgate nand (lambda (x y) (not (and x y))))

(defgate not not :arity 1)




;;;; Circuits complexes


(defclass complex-circuit (component)
  ((subcomponents  :reader complex-circuit-subs
		   :initarg :subs))
  (:documentation "circuits with various inputs, outputs,
                  and substructures"))


(defun make-complex-circuit (subs nb-in nb-out)
  (make-instance 'complex-circuit
		 :subs subs
		 :nb-in nb-in
		 :nb-out nb-out))



(defgeneric def-output ((cc complex-circuit) (i integer)
			(sc component) (j integer))
  (:documentation 
   "(def-output cc i sub j) defines the i-th output of cc as the j-th
output
of sub"))

(defgeneric branch-input ((cc complex-circuit) (i integer)
			  (sc component) (j integer))
  (:documentation 
   "(branch-input cc i sub j) branches the i-th input of cc to the j-th
intput
of sub"))


(defgeneric short-circuit ((cc complex-circuit) (i integer) (j integer))
  (:documentation 
   "(short-circuit cc i j) branches the i-th input of cc to it's j-th
output"))




(defmethod compute-temp-state ((c complex-circuit))
  (mapc #'compute-temp-state (complex-circuit-subs c)))

(defmethod update ((c complex-circuit))
  (mapc #'update (complex-circuit-subs c)))


(defmethod branch-input  ((cc complex-circuit) (i integer)
			  (sc component) (j integer))
  (setf (svref (component-inputs sc) j)
	#'(lambda () (funcall (svref (component-inputs cc)i)))))


(defmethod def-output  ((cc complex-circuit) (i integer)
			(sc component) (j integer))
  (setf (svref (component-outputs cc) i)
	#'(lambda ()
	    (output-state sc j))))


(defmethod short-circuit  ((cc complex-circuit) (i integer) (j integer))
  (setf (svref (component-outputs cc) j)
	#'(lambda () 
	    (funcall  (svref (component-inputs cc) i)))))


;;;; flip-flop

(defun make-flip-flop ()
  (let* ((g1 (make-nor-gate))
	 (g2 (make-nor-gate))
	 (f (make-complex-circuit (list g1 g2) 2 2)))
    (branch-input f 0 g1 0)
    (branch-input f 1 g2 1)
    (connect g1 0 g2 0)
    (connect g2 0 g1 1)
    (def-output f 0 g1 0)
    (def-output f 1 g2 0)
    f))


(defmethod  parallel ((comp1 component) (comp2 component))
  (let ((n1 (component-nb-in comp1))
	(n2 (component-nb-in comp2))
	(p1 (component-nb-out comp1))
	(p2 (component-nb-out comp2)))
    (let ((comp (make-complex-circuit (list comp1 comp2)
				      (+ n1 n2)
				      (+ p1 p2))))
      (dotimes (i n1 t)
	(branch-input comp i comp1 i))
      (dotimes (i n2 t)
	(branch-input comp (+ i n1) comp2 i)) 
      (dotimes (i p1 t)
	(def-output comp i comp1 i))
      (dotimes (i p2 t)
	(def-output comp (+ i p1) comp2 i))
      comp)))


(defmethod serie ((comp1 component) (comp2 component))
  (let ((n1 (component-nb-in comp1))
	(n2 (component-nb-in comp2))
	(p1 (component-nb-out comp1))
	(p2 (component-nb-out comp2)))
    (assert (= p1 n2))
    (let ((comp (make-complex-circuit (list comp1 comp2)
				      n1 p2)))
      (dotimes (i n1 t)
	(branch-input comp i comp1 i))
      (dotimes (i p2 t)
	(def-output comp i comp2 i))
      (dotimes (i p1 t)
	(connect comp1 i comp2 i))
      comp)))





(defun make-add-one-bit ()
  (let* ((c1 (make-or-gate))
	 (c2 (make-and-gate))
	 (c3 (make-and-gate))
	 (c4 (make-or-gate))
	 (r1 (make-xor-gate))
	 (r2 (make-xor-gate))
	 (f (make-complex-circuit (list c1 c2 c3 c4 r1 r2) 3 2)))
    ;;; branchements pour la retenue
    (branch-input f 1 c1 0)
    (branch-input f 2 c1 1)
    (branch-input f 1 c2 0)
    (branch-input f 2 c2 1)
    (branch-input f 0 c3 0)
    (connect c1 0 c3 1)
    (connect c3 0 c4 0)
    (connect c2 0 c4 1)
    (def-output f 0 c4 0)
    ;;; branchements pour le resultat 
    (branch-input f 1 r1 0)
    (branch-input f 2 r1 1)
    (branch-input f 0 r2 0)
    (connect r1 0 r2 1)
    (def-output f 1 r2 0)
    f))



(defun make-add-n-bit( n )
  ( assert (> n 0))
  (defun aux ( box temp acc )
    (if(= acc n)
       temp
       (let ((f (make-complex-circuit(list box temp)
				   (+ * + acc 1 2 1)
				   (+ acc 2))))
	 (branch-input f (* 2 acc) temp (* - 1 acc 2)) ;;; liaison avec la
retenue 
	 ;;; identification des entrees entre les additionneurs acc et acc-1
bits
	 (dotimes (i (+ acc 1) t)	 
	   (branch-input f (* 2 i) temp (* 2 i)))
	 (dotimes (i (+ acc 1) t)
	    (branch-input f (+ * 2 i 1) temp (+ * 2 i 1)))
	 ;;; raccordement du nouvel additionneur
	 (branch-input f (* - 1 acc 2) box 0)
	 (branch-input f (- * 2 acc 1) box 1)
	 (connect temp 0 box 2)
	 (def-output f 0 box 0)
	 (def-output f 1 box 1)
	 ;;;identification des sorties entre les additionneurs acc et acc-1
bits
	 (dotimes (i acc t)
	   (def-output f (+ i 2) temp (+ i 1)))
	 (aux (make-add-one-bit) f (+ acc 1)))))
  (aux (make-add-one-bit) (make-add-one-bit) 1))


---------------[ demo.lisp]-------------------------------------
(load "projet")
(use-package 'circuits)



;;;; essai de add-bit()

;(defvar *x* (make-switch))
;(defvar *y* (make-switch))
;(defvar *c* (make-switch))
;(defvar *addbit* (make-add-one-bit))

;(switch-toggle *x*)
;(switch-toggle *y*)
;(switch-toggle *c*)

;(comp-describe *x* )
;(comp-describe *y* )
;(comp-describe *c* )
;(connect *x* 0 *addbit* 0)
;(connect *y* 0 *addbit* 1)
;(connect *c* 0 *addbit* 2)

;(simulate *addbit* 1)

;;;;; essai de add-n-bit

(defvar *x0* (make-switch))
(defvar *y0* (make-switch))
(defvar *x1* (make-switch))
(defvar *y1* (make-switch))
(defvar *x2* (make-switch))
(defvar *y2* (make-switch))
(defvar *x3* (make-switch))
(defvar *y3* (make-switch))
(defvar *carry* (make-switch))
(defvar *add3bit* (make-add-n-bit 3))

From: Stig Hemmer
Subject: Re: problem with my small program
Date: 
Message-ID: <ekvd869mhtw.fsf@gnoll.pvv.ntnu.no>
Error message containing:
>(KERNEL:TWO-ARG-+ NIL NIL)

While I can't claim to have taken the time to understand you code, a
quick look for +'s in your code shows forms like (+ * + acc 1 2 1) and
(+ * 2 i 1).  Since * and + does in fact have variable bindings, these
forms gives odd error messages.

Stig Hemmer,                      perl -e 'print "Not a Perl hacker.\n"'
Jack of a Few Trades.
"Just when you accept that life's a bitch, it has puppies."
From: Rainer Joswig
Subject: Re: problem with my small program
Date: 
Message-ID: <joswig-2711981305270001@pbg3.lavielle.com>
In article <················@emi.u-bordeaux.fr>, Yann Planchais
<········@emi.u-bordeaux.fr> wrote:

> (defgeneric comp-describe ((c component) &key (stream t)))

DEFGENERIC should have a different parameter list.
Above code does not work.

> (defun make-add-n-bit( n )
>   ( assert (> n 0))
>   (defun aux ( box temp acc )
>     (if(= acc n)
>        temp
>        (let ((f (make-complex-circuit(list box temp)
>                                    (+ * + acc 1 2 1)
>                                    (+ acc 2))))
>          (branch-input f (* 2 acc) temp (* - 1 acc 2)) ;;; liaison avec la
...

You cannot use nested defuns. Use LABELS or FLET.

I don't understand stuff like  "(+ * + acc 1 2 1)", "(* - 1 acc 2)", etc.
What values should the variables "*", "-", and "+" have?

-- 
http://www.lavielle.com/~joswig
From: Paul Meurer
Subject: Re: problem with my small program
Date: 
Message-ID: <365ea7c9.259683575@nntp.uib.no>
On Fri, 27 Nov 1998 13:05:27 +0100, ······@lavielle.com (Rainer
Joswig) wrote:

>In article <················@emi.u-bordeaux.fr>, Yann Planchais
><········@emi.u-bordeaux.fr> wrote:
>

>You cannot use nested defuns. Use LABELS or FLET.
>
>I don't understand stuff like  "(+ * + acc 1 2 1)", "(* - 1 acc 2)", etc.
>What values should the variables "*", "-", and "+" have?
>

Maybe he does not like parentheses and has dropped them from

(+ (* (+ acc 1) 2) 1)

and 

(* (- 1 acc) 2).

Just a wild guess.

Paul