From: David Steuber
Subject: What's so special about IF?
Date: 
Message-ID: <87zn08w8bs.fsf@david-steuber.com>
The CLHS states that IF is a Special Operator.  But what if there was
no IF?  Don't ask my why I was thinking about this.  Just for fun, I
decided to see if I could use the Macros AND and OR along with the
function NOT to see if I could emulate IF:

(defmacro my-if (test then &optional (else nil))
  (let ((b (gensym)))
    `(let ((,b ,test))
       (or (and ,b ,then)
           (and (not ,b) ,else)))))

Some of the inspiration came from a digital logic course I once took
which reduced everything in a computer to several fundamental gates.

I know it's trivial, but I find this a rather eloquent answer to what
makes Lisp special.

-- 
An ideal world is left as an excercise to the reader.
   --- Paul Graham, On Lisp 8.1

From: Artie Gold
Subject: Re: What's so special about IF?
Date: 
Message-ID: <32psneF3pjjn9U1@individual.net>
David Steuber wrote:
> The CLHS states that IF is a Special Operator.  But what if there was
> no IF?  Don't ask my why I was thinking about this.  Just for fun, I
> decided to see if I could use the Macros AND and OR along with the
> function NOT to see if I could emulate IF:
> 
> (defmacro my-if (test then &optional (else nil))
>   (let ((b (gensym)))
>     `(let ((,b ,test))
>        (or (and ,b ,then)
>            (and (not ,b) ,else)))))
> 
> Some of the inspiration came from a digital logic course I once took
> which reduced everything in a computer to several fundamental gates.
> 
> I know it's trivial, but I find this a rather eloquent answer to what
> makes Lisp special.
> 
Hmmmm...

Can you come up with an implementation for `or' in an `if'-less Lisp?

Cheers,
--ag

-- 
Artie Gold -- Austin, Texas
http://it-matters.blogspot.com (new post 12/5)
http://www.cafepress.com/goldsays
From: jtdubs
Subject: Re: What's so special about IF?
Date: 
Message-ID: <1103613943.730087.157740@f14g2000cwb.googlegroups.com>
Artie Gold wrote:
> David Steuber wrote:
> > The CLHS states that IF is a Special Operator.  But what if there
was
> > no IF?  Don't ask my why I was thinking about this.  Just for fun,
I
> > decided to see if I could use the Macros AND and OR along with the
> > function NOT to see if I could emulate IF:
> >
> > (defmacro my-if (test then &optional (else nil))
> >   (let ((b (gensym)))
> >     `(let ((,b ,test))
> >        (or (and ,b ,then)
> >            (and (not ,b) ,else)))))
> >
> > Some of the inspiration came from a digital logic course I once
took
> > which reduced everything in a computer to several fundamental
gates.
> >
> > I know it's trivial, but I find this a rather eloquent answer to
what
> > makes Lisp special.
> >
> Hmmmm...
>
> Can you come up with an implementation for `or' in an `if'-less Lisp?
(or a b) == (not (and (not a) (not b)))

Justin Dubs
From: Alexander Schmolck
Subject: Re: What's so special about IF?
Date: 
Message-ID: <yfshdmgj9ww.fsf@black4.ex.ac.uk>
"jtdubs" <······@eos.ncsu.edu> writes:

> Artie Gold wrote:
>> Can you come up with an implementation for `or' in an `if'-less Lisp?
> (or a b) == (not (and (not a) (not b)))

Only in logic. Something along these lines ought to do the job, though.

(defmacro or* (a b)
    (let ((a* (gensym))
          (b* (gensym))
          (table (gensym)))
  `(let* ((,a* ,a)
          (,b* ,b)
          (,table (list (cons '(t)  ,a*)
                        (cons '(t . t)  ,a*)
                        (cons '(nil . t)  ,b*))))
     (cdr (assoc (cons (not (not ,a*)) (not (not ,b*)))  ,table :test #'equal))
     )))

CL-USER> (or* 'a 'b)
A
CL-USER> (or* nil 'b)
B
CL-USER> (or* nil nil)
NIL


'as
From: Artie Gold
Subject: Re: What's so special about IF?
Date: 
Message-ID: <32rgrlF3q8us7U1@individual.net>
Alexander Schmolck wrote:
> "jtdubs" <······@eos.ncsu.edu> writes:
> 
> 
>>Artie Gold wrote:
>>
>>>Can you come up with an implementation for `or' in an `if'-less Lisp?
>>
>>(or a b) == (not (and (not a) (not b)))
> 
> 
> Only in logic. Something along these lines ought to do the job, though.
> 
> (defmacro or* (a b)
>     (let ((a* (gensym))
>           (b* (gensym))
>           (table (gensym)))
>   `(let* ((,a* ,a)
>           (,b* ,b)
>           (,table (list (cons '(t)  ,a*)
>                         (cons '(t . t)  ,a*)
>                         (cons '(nil . t)  ,b*))))
>      (cdr (assoc (cons (not (not ,a*)) (not (not ,b*)))  ,table :test #'equal))
>      )))
> 
> CL-USER> (or* 'a 'b)
> A
> CL-USER> (or* nil 'b)
> B
> CL-USER> (or* nil nil)
> NIL
> 
> 
> 'as

The problem is that `b' gets evaluated unconditionally -- which is not 
what you want.

HTH,
--ag

-- 
Artie Gold -- Austin, Texas
http://it-matters.blogspot.com (new post 12/5)
http://www.cafepress.com/goldsays
From: Brian Downing
Subject: Re: What's so special about IF?
Date: 
Message-ID: <M74yd.221299$5K2.176930@attbi_s03>
In article <···············@black4.ex.ac.uk>,
Alexander Schmolck  <··········@gmx.net> wrote:
> Only in logic. Something along these lines ought to do the job, though.
> 
> (defmacro or* (a b)
>     (let ((a* (gensym))
>           (b* (gensym))
>           (table (gensym)))
>   `(let* ((,a* ,a)
>           (,b* ,b)
>           (,table (list (cons '(t)  ,a*)
>                         (cons '(t . t)  ,a*)
>                         (cons '(nil . t)  ,b*))))
>      (cdr (assoc (cons (not (not ,a*)) (not (not ,b*)))  ,table :test #'equal))
>      )))
> 
> CL-USER> (or* 'a 'b)
> A
> CL-USER> (or* nil 'b)
> B
> CL-USER> (or* nil nil)
> NIL

Unfortunatly this fails the critical "destroy-the-world" test:

CL-USER> (or t (destroy-the-world))
T
CL-USER> (or* t (destroy-the-world))
World destroyed!
   [Condition of type SIMPLE-ERROR]

(Also, the built-in AND and OR can take more than two operators.)

-bcd
-- 
*** Brian Downing <bdowning at lavos dot net> 
From: Brian Downing
Subject: Re: What's so special about IF?
Date: 
Message-ID: <sf4yd.269705$HA.256219@attbi_s01>
In article <···············@black4.ex.ac.uk>,
Alexander Schmolck  <··········@gmx.net> wrote:
> Only in logic. Something along these lines ought to do the job, though.
> 
> (defmacro or* (a b)
>     (let ((a* (gensym))
>           (b* (gensym))
>           (table (gensym)))
>   `(let* ((,a* ,a)
>           (,b* ,b)
>           (,table (list (cons '(t)  ,a*)
>                         (cons '(t . t)  ,a*)
>                         (cons '(nil . t)  ,b*))))
>      (cdr (assoc (cons (not (not ,a*)) (not (not ,b*)))  ,table :test #'equal))
>      )))
> 
> CL-USER> (or* 'a 'b)
> A
> CL-USER> (or* nil 'b)
> B
> CL-USER> (or* nil nil)
> NIL

Unfortunatly this fails the critical "destroy-the-world" test:

CL-USER> (or t (destroy-the-world))
T
CL-USER> (or* t (destroy-the-world))
World destroyed!
   [Condition of type SIMPLE-ERROR]

(Also, the built-in AND and OR can take more than two arguments.)

-bcd
-- 
*** Brian Downing <bdowning at lavos dot net> 
From: Alexander Schmolck
Subject: Re: What's so special about IF?
Date: 
Message-ID: <yfsu0qed37r.fsf@black4.ex.ac.uk>
Brian Downing <·············@lavos.net> writes:

> In article <···············@black4.ex.ac.uk>,
> Alexander Schmolck  <··········@gmx.net> wrote:
>> Only in logic. Something along these lines ought to do the job, though.
>> 
>> (defmacro or* (a b)
>>     (let ((a* (gensym))
>>           (b* (gensym))
>>           (table (gensym)))
>>   `(let* ((,a* ,a)
>>           (,b* ,b)
>>           (,table (list (cons '(t)  ,a*)
>>                         (cons '(t . t)  ,a*)
>>                         (cons '(nil . t)  ,b*))))
>>      (cdr (assoc (cons (not (not ,a*)) (not (not ,b*)))  ,table :test #'equal))
>>      )))
>> 
>> CL-USER> (or* 'a 'b)
>> A
>> CL-USER> (or* nil 'b)
>> B
>> CL-USER> (or* nil nil)
>> NIL
>  
> Unfortunatly this fails the critical "destroy-the-world" test:
>
> CL-USER> (or t (destroy-the-world))
> T
> CL-USER> (or* t (destroy-the-world))
> World destroyed!
>    [Condition of type SIMPLE-ERROR]

Argh, how embarrassing -- should have known better than to post anything in a
state of insomnia. Anyway here we go again (still haven't had much sleep, so
for saftey critical code best stick with the OR that comes supplied with your
lisp version):

(defmacro or* (a b)
    (let ((a* (gensym))
          (bf* (gensym))
          (b* (gensym))
          (table (gensym)))
  `(let* ((,a* ,a)
          (,bf* (lambda () ,b))
          (,table (list (cons nil   (lambda () ,a*))
                        (cons t     (lambda () (funcall ,bf*))))))
     (funcall (cdr (assoc (not ,a*) ,table)))
     )))

(defmacro with-results (() &body body)
  (cons 'list (mapcar (lambda (form) `(list ',form '=> ,form))
                      body)))

(let ((a 1)
      (b 0))
  (with-results ()
    (or* (incf a) (/ (incf b) 0))
    (or* nil (incf b))
    (or* nil nil)))
=>(((OR* (INCF A) (/ (INCF B) 0)) => 2)
   ((OR* NIL (INCF B)) => 1)
   ((OR* NIL NIL) => NIL))

> (Also, the built-in AND and OR can take more than two arguments.)

Sure, but these are left as an excersise to the more devoted reader (hence
"along these lines").

'as
From: Kaz Kylheku
Subject: Re: What's so special about IF?
Date: 
Message-ID: <1103650803.562160.53540@z14g2000cwz.googlegroups.com>
jtdubs wrote:
> Artie Gold wrote:
> > Can you come up with an implementation for `or' in an `if'-less
Lisp?
> (or a b) == (not (and (not a) (not b)))
>
> Justin Dubs

Don't forget that OR is used for evaluation control, not just for
computing a boolean result. It must keep evaluating its arguments left
to right until it encounters one which is other than NIL. That value is
then propagated as the result of the OR, and no additional arguments
are evaluated.

As to Artie's question, my implementation would just be:

(defmaro my-or (&body args) `(or ,@args))
He said IF-less Lisp; he didn't say OR-less. :)
From: Svein Ove Aas
Subject: Re: What's so special about IF?
Date: 
Message-ID: <cq8p57$b89$1@services.kq.no>
start quoting jtdubs :

> Artie Gold wrote:
>> David Steuber wrote:
>> > The CLHS states that IF is a Special Operator.  But what if there
> was
>> > no IF?  Don't ask my why I was thinking about this.  Just for fun,
> I
>> > decided to see if I could use the Macros AND and OR along with the
>> > function NOT to see if I could emulate IF:
>> >
>> > (defmacro my-if (test then &optional (else nil))
>> >   (let ((b (gensym)))
>> >     `(let ((,b ,test))
>> >        (or (and ,b ,then)
>> >            (and (not ,b) ,else)))))
>> >
>> > Some of the inspiration came from a digital logic course I once
> took
>> > which reduced everything in a computer to several fundamental
> gates.
>> >
>> > I know it's trivial, but I find this a rather eloquent answer to
> what
>> > makes Lisp special.
>> >
>> Hmmmm...
>>
>> Can you come up with an implementation for `or' in an `if'-less Lisp?
> (or a b) == (not (and (not a) (not b)))
> 
And given that 'and' is also implemented using if, try it without and.
In fact, try it without any control-type forms at all.
(I'm not sure, but it just might be possible, if somewhat hair-raising)
From: jtdubs
Subject: Re: What's so special about IF?
Date: 
Message-ID: <1103613899.703129.153950@f14g2000cwb.googlegroups.com>
Artie Gold wrote:
> David Steuber wrote:
> > The CLHS states that IF is a Special Operator.  But what if there
was
> > no IF?  Don't ask my why I was thinking about this.  Just for fun,
I
> > decided to see if I could use the Macros AND and OR along with the
> > function NOT to see if I could emulate IF:
> >
> > (defmacro my-if (test then &optional (else nil))
> >   (let ((b (gensym)))
> >     `(let ((,b ,test))
> >        (or (and ,b ,then)
> >            (and (not ,b) ,else)))))
> >
> > Some of the inspiration came from a digital logic course I once
took
> > which reduced everything in a computer to several fundamental
gates.
> >
> > I know it's trivial, but I find this a rather eloquent answer to
what
> > makes Lisp special.
> >
> Hmmmm...
>
> Can you come up with an implementation for `or' in an `if'-less Lisp?
(or a b) == (not (and (not a) (not b)))

Justin Dubs
From: Jeff M.
Subject: Re: What's so special about IF?
Date: 
Message-ID: <1103649420.596781.173260@c13g2000cwb.googlegroups.com>
I think the more important question is whether or not IF is a macro
that expands to COND, or the other way around. In LW and CCL, COND
expands to IF, and I assume it would be the same in all
implementations.

My question would be "why"? It is a speed issue or simplicity? Have
past implementations done it the other way around? Also, sources on the
web that discuss pure Lisp or the 7 needed symbols, always use COND
instead of IF. If COND is described from IF in Lisp implementations,
why isn't IF one of those symbols and not COND?

Jeff M.
From: Pascal Bourguignon
Subject: Re: What's so special about IF?
Date: 
Message-ID: <87oegntu95.fsf@thalassa.informatimago.com>
"Jeff M." <·······@gmail.com> writes:

> I think the more important question is whether or not IF is a macro
> that expands to COND, or the other way around. In LW and CCL, COND
> expands to IF, and I assume it would be the same in all
> implementations.
> 
> My question would be "why"? It is a speed issue or simplicity? Have
> past implementations done it the other way around? Also, sources on the
> web that discuss pure Lisp or the 7 needed symbols, always use COND
> instead of IF. If COND is described from IF in Lisp implementations,
> why isn't IF one of those symbols and not COND?

For historical reasons. The first lisp was defined with COND, not with IF.


;;****************************************************************************
;;FILE:               aim-8.lisp
;;LANGUAGE:           Common-Lisp
;;SYSTEM:             Common-Lisp
;;USER-INTERFACE:     NONE
;;DESCRIPTION
;;    
;;    Implements the LISP described in AIM-8 in Common-Lisp.
;;    Usage:  (load "aim-8.lisp") 
;;            (aim-8:repl)
;;    Then at the aim-8 prompt, you have LISP, plus:
;;       (DEFINE name sexp)     corresponding to =
;;       (RELOAD)               to reload aim-8 if you edit it.
;;       (DUMP-ENVIRONMENT)     to dump the defined symbols.
;;       (LOAD "path")          to load an aim-8 source. Try "aim-8.aim-8".
;;    
;;AUTHORS
;;    <PJB> Pascal Bourguignon <···@informatimago.com>
;;MODIFICATIONS
;;    2004-10-24 <PJB> Created.
;;BUGS
;;LEGAL
;;    GPL
;;    
;;    Copyright Pascal Bourguignon 2004 - 2004
;;    
;;    This program is free software; you can redistribute it and/or
;;    modify it under the terms of the GNU General Public License
;;    as published by the Free Software Foundation; either version
;;    2 of the License, or (at your option) any later version.
;;    
;;    This program is distributed in the hope that it will be
;;    useful, but WITHOUT ANY WARRANTY; without even the implied
;;    warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
;;    PURPOSE.  See the GNU General Public License for more details.
;;    
;;    You should have received a copy of the GNU General Public
;;    License along with this program; if not, write to the Free
;;    Software Foundation, Inc., 59 Temple Place, Suite 330,
;;    Boston, MA 02111-1307 USA
;;****************************************************************************
;;    
;; AIM-8 -- 23 MARCH 1959 -- J. MCCARTHY


;; (IN-PACKAGE "COMMON-LISP-USER")
;; (defpackage "LISP-1"
;;   (:use "COMMON-LISP")
;;   (:export "DEFINE" "LAMBDA" "LABEL"
;;            "COND" "AND" "OR" "NOT"
;;            "COMBINE" "FIRST" "REST"
;;            "NULL" "ATOM" "EQ" 
;;            "NIL" "T" "QUOTE"));;LISP-1



;;(funcall (LABEL fact (lambda (x) (cond ((= 1 x) 1) (t (* x (fact (1- x))))))) 6)




(DEFPACKAGE "AIM-8"
  (:USE "COMMON-LISP")
  (:EXPORT "REPL")
  (:DOCUMENTATION
   "Implements the lisp of AIM-8 -- 23 MARCH 1959 -- J. McCarthy"));;AIM-8
(IN-PACKAGE "AIM-8")


(DEFPACKAGE "AIM-8-USER"
  (:USE)
  (:IMPORT-FROM "AIM-8"
                "DEFINE" "LAMBDA" "LABEL"
                "COND"  "COMBINE" "FIRST" "REST"
                "NULL" "ATOM" "EQ" "NIL" "T" "QUOTE"));;AIM-8-USER

(DEFPARAMETER *ENVIRONMENT* (MAKE-HASH-TABLE :TEST (FUNCTION EQ)))
(DEFMACRO DEF     (NAME)       `(GETHASH ,NAME *ENVIRONMENT*))
(DEFUN   %BOUNDP  (NAME) (MULTIPLE-VALUE-BIND (VAL BND) (DEF NAME)
                          (DECLARE (IGNORE VAL)) BND))
(DEFMACRO DEFINE  (NAME VALUE) `(SETF (GETHASH ',NAME *ENVIRONMENT*) ',VALUE))
(DEFUN   FDEFINE  (NAME VALUE)  (SETF (GETHASH NAME *ENVIRONMENT*) VALUE))

(DEFINE NIL ())
(DEFINE F   ())
(DEFINE T   T)
(DEFINE AND     (LAMBDA (A B) (COND (A (COND (B T) (T NIL))) (T NIL))))
(DEFINE OR      (LAMBDA (A B) (COND (A T) (B T) (T NIL))))
(DEFINE NOT     (LAMBDA (A)   (COND (A NIL) (T NIL))))
(DEFINE MAPLIST 
        (LAMBDA (X F)
          (COND ((NULL X) NIL)
                (T (COMBINE (F X) (MAPLIST (REST X) F))))))
(DEFINE SUBST 
        (LAMBDA (X Y A)
          (COND ((NULL A) NIL)
                ((ATOM A) (COND ((EQ Y A) X) (T A)))
                (T (COMBINE (SUBST X Y (FIRST A))
                            (SUBST X Y (REST A))))
                )));;SUBST


(DEFUN %SUBST (X Y A)
  (COND ((NULL A) NIL)
        ((ATOM A) (COND ((EQ Y A) X) (T A)))
        (T (CONS (%SUBST X Y (FIRST A)) (%SUBST X Y (REST A))))))


(DEFUN %SUBSQ (X Y Z)
  (COND ((NULL Z) NIL)
        ((ATOM Z) (COND ((EQ Y Z) X)  (T Z)))
        ((EQ (FIRST Z) 'QUOTE) Z)
        (T (CONS (%SUBSQ X Y (FIRST Z)) (%SUBSQ X Y (REST Z))))));;%SUBSQ


(DEFUN %EVCON (C)
  (COND ((%EVAL (FIRST (FIRST C))) (%EVAL (FIRST (REST (FIRST C)))))
        (T (%EVCON (REST C)))))


(DEFUN %EVLAM (VARS EXP ARGS)
  (COND ((NULL VARS) (%EVAL EXP))
        (T (%EVLAM (REST VARS) (%SUBSQ (FIRST ARGS) (FIRST VARS) EXP)
                   (REST ARGS)))))


(DEFUN %APPLY (F ARGS) (%EVAL (CONS F ARGS)))


(DEFUN %EVAL (E)
  (COND
    ;; begin extensions:
    ((ATOM E) (COND ((%BOUNDP E) (DEF E))
                    (T (ERROR "Undefined: ~A" (FIRST E)))))
    ;; end extensions.
    (T (CASE (FIRST E)
         ((NULL)    (NULL  (%EVAL (FIRST (REST E)))))
         ((ATOM)    (ATOM  (%EVAL (FIRST (REST E)))))
         ((QUOTE)   (FIRST (REST E)))
         ((EQ)      (EQ    (%EVAL (FIRST (REST E)))
                           (%EVAL (FIRST (REST (REST E))))))
         ((COMBINE) (CONS  (%EVAL (FIRST (REST E)))
                           (%EVAL (FIRST (REST (REST E))))))
         ((FIRST)   (FIRST (%EVAL (FIRST (REST E)))))
         ((REST)    (REST  (%EVAL (FIRST (REST E)))))
         ((COND)    (%EVCON (REST E)))
         ;; begin extensions:
         ((LOAD)    (LOAD  (%EVAL (FIRST (REST E)))))
         ((PRINT)   (PRINT (%EVAL (FIRST (REST E)))))
         ((READ)    (READ))
         (OTHERWISE
          (COND
            ((ATOM (FIRST E))
             (COND ((%BOUNDP (FIRST E)) (%APPLY (DEF (FIRST E)) (REST E)))
                   (T (ERROR "Undefined: ~A" (FIRST E)))))
            ;; end extensions.
            (T (CASE (FIRST (FIRST E))
                 ((LAMBDA) (%EVLAM (FIRST (REST (FIRST E)))
                              (FIRST (REST (REST (FIRST E))))
                              (REST E)))
                 ((LABEL) (%EVAL (CONS (%SUBST (FIRST E)
                                               (FIRST (REST (FIRST E)))
                                               (FIRST (REST (REST (FIRST E)))))
                                       (REST E))))
                 (OTHERWISE (ERROR "Invalid: ~A" (FIRST E)))))))))));;%EVAL



(DEFUN HELP ()
  (FORMAT T "~&You've got:  
    DEFINE LAMBDA LABEL
    COND AND OR NOT  COMBINE FIRST REST
    NULL ATOM EQ NIL T QUOTE
    QUIT"));;HELP


(DEFUN REPL ()
  (LET ((*PACKAGE* (FIND-PACKAGE "AIM-8")))
    (HELP)
    (LOOP
       (TERPRI)
       (PRINC "AIM-8> ")
       (HANDLING-ERRORS
        (LET ((SEXP (READ)))
          (COND
            ((EQUAL SEXP '(QUIT))
             (FORMAT T "GOOD BYE") (RETURN-FROM REPL))
            ((EQUAL SEXP '(RELOAD))
             (LOAD "aim-8") (REPL) (RETURN-FROM REPL))
            ((EQUAL SEXP '(DUMP-ENVIRONMENT))
             (FORMAT T ·······@A = ~A~%~}" 
                     (LET ((RES '()))
                       (MAPHASH (LAMBDA (K V) (PUSH (LIST K V) RES)) 
                                *ENVIRONMENT*) RES)))
            ((AND (LISTP SEXP) (EQ (FIRST SEXP) 'DEFINE))
             (FDEFINE (SECOND SEXP) (THIRD SEXP))
             (FORMAT T "~A" (SECOND SEXP)))
            (T 
             (FORMAT T "~S" (%EVAL SEXP))))))))
  (TERPRI)
  (VALUES));;REPL
         


;; (in-package "COMMON-LISP-USER")
;; (aim-8:repl)


#||
(define FF (lambda (X) (COND ((OR (NULL X) (ATOM X)) X) (T (FF (FIRST X))))))
(FF (quote (A B)))
;; A
(FF (quote ((A B) C)))
;; A
(FF (quote (((A) B) C)))
;; A
(ff '(()()(()()())((((a)))b)))
;; NIL
(define ff1 (lambda (X) (COND ((OR (NULL X) (ATOM X)) X) 
                         (T (cond ((FF1 (FIRST X)) (FF1 (FIRST X)))
                                  (t (FF1 (REST X))))))))
(ff1 '(()()(()()())((((a)))b)))
A
v||#


#||
(SUBST (quote TOTO) (quote X) (quote (COND ((EQ X A) A) (T NIL))))
;; (COND ((EQ TOTO A) A) (T NIL))
||#


#||         



(define diff 
        (lambda (y x)
          (cond 
            ((atom y) 
             (cond ((eq y x) (quote one))
                   (t (quote zero))))
            ((eq (first y) (quote plus))
             (combine (quote plus) (maplist (rest y) (lambda (a) (diff (first a) x)))))
            ((eq (first y) (quote times))
             (combine (quote plus)
                   (maplist 
                    (rest y) 
                    (lambda (a) (combine (quote times)
                                 (maplist
                                  (rest y)
                                  (lambda (w) (cond ((not (eq a w)) (first w))
                                               (t (diff (first w) x))
                                               )))))))))));;diff

(diff (quote (plus (times 2 x) (times 2 x x))) (quote x))
;; (plus (plus (times zero x) (times 2 one))
;;       (plus (times zero x x) (times 2 one x) (times 2 x one)))
|#
 


;;;; aim-8.lisp                       --                     --          ;;;;


-- 
__Pascal Bourguignon__                     http://www.informatimago.com/
Until real software engineering is developed, the next best practice
is to develop with a dynamic system that has extreme late binding in
all aspects. The first system to really do this in an important way
is Lisp. -- Alan Kay
From: lin8080
Subject: Re: What's so special about IF?
Date: 
Message-ID: <41CA08DA.8E3770BE@freenet.de>
Pascal Bourguignon schrieb:

> ;;****************************************************************************
> ;;FILE:               aim-8.lisp
> ;;LANGUAGE:           Common-Lisp
> ;;SYSTEM:             Common-Lisp
> ;;USER-INTERFACE:     NONE
> ;;DESCRIPTION

Thank You. I missed this.

lin
From: Luis Oliveira
Subject: Re: What's so special about IF?
Date: 
Message-ID: <kseu92-7l8.ln1@netman.ath.cx>
Pascal Bourguignon skribis:
> (DEFUN HELP ()
>  (FORMAT T "~&You've got:  
>    DEFINE LAMBDA LABEL
>    COND AND OR NOT  COMBINE FIRST REST
>    NULL ATOM EQ NIL T QUOTE
>    QUIT"));;HELP

I have a small question. Why did you write your code all in caps? Do you
still write it that way? Why? (oops, make that small *questions*)

Merry christmas,

-- 
Luís Oliveira
Reply-To: luismbo (@) netcabo (.) pt
Equipa Portuguesa do Translation Project
http://www2.iro.umontreal.ca/~pinard/po/registry.cgi?team=pt
From: Jeff
Subject: Re: What's so special about IF?
Date: 
Message-ID: <3rlBd.732173$mD.511732@attbi_s02>
Luis Oliveira wrote:

> Pascal Bourguignon skribis:
> > (DEFUN HELP ()
> >  (FORMAT T "~&You've got:  
> >    DEFINE LAMBDA LABEL
> >    COND AND OR NOT  COMBINE FIRST REST
> >    NULL ATOM EQ NIL T QUOTE
> >    QUIT"));;HELP
> 
> I have a small question. Why did you write your code all in caps? Do
> you still write it that way? Why? (oops, make that small questions)
> 

Just a guess, but I'd bet that was copied/pasted from a document and
not hand-typed :)

Jeff M.

-- 
http://www.retrobyte.org
··············@gmail.com
From: Pascal Bourguignon
Subject: Re: What's so special about IF?
Date: 
Message-ID: <871xd5azkt.fsf@thalassa.informatimago.com>
Luis Oliveira <·············@deadspam.com> writes:

> ourguignon skribis:
> > (DEFUN HELP ()
> >  (FORMAT T "~&You've got:  
> >    DEFINE LAMBDA LABEL
> >    COND AND OR NOT  COMBINE FIRST REST
> >    NULL ATOM EQ NIL T QUOTE
> >    QUIT"));;HELP
> 
> I have a small question. Why did you write your code all in caps? Do you
> still write it that way? Why? (oops, make that small *questions*)

You quoted the wrong part:

> ;; AIM-8 -- 23 MARCH 1959 -- J. MCCARTHY
                       ^^^^

-- 
__Pascal_Bourguignon__               _  Software patents are endangering
()  ASCII ribbon against html email (o_ the computer industry all around
/\  1962:DO20I=1.100                //\ the world http://lpf.ai.mit.edu/
    2001:my($f)=`fortune`;          V_/   http://petition.eurolinux.org/
From: mikel
Subject: Re: What's so special about IF?
Date: 
Message-ID: <l%_xd.970$5R.815@newssvr21.news.prodigy.com>
Jeff M. wrote:
> I think the more important question is whether or not IF is a macro
> that expands to COND, or the other way around. In LW and CCL, COND
> expands to IF, and I assume it would be the same in all
> implementations.
> 
> My question would be "why"? 

If nothing else, for brain-tickling fun.

A language consisting of two rewrite rules called "combinators", where 
the two rules are conventionally called S and K, is turing-complete:

(defun S (x y z)
   (funcall (funcall x z)
            (funcall y z)))

(defun K (x y) x)

  You can use S and K to implement anything computable, including IF 
and, slightly brain-bendingly, the Y combinator, which implements recursion.

The above may not be quite correct; I'm rather sick at the moment, and 
my brain is not working up to even its normal slow capacity. Google for 
"combinators" if this sort of thing pushes your fun buttons.
From: Clive Tong
Subject: Re: What's so special about IF?
Date: 
Message-ID: <uwtvc2du0.fsf@scientia.com>
David Steuber <·····@david-steuber.com> writes:

> (defmacro my-if (test then &optional (else nil))
>   (let ((b (gensym)))
>     `(let ((,b ,test))
>        (or (and ,b ,then)
>            (and (not ,b) ,else)))))
> 

This macro doesn't deal properly with multiple values owing to the way
OR deals with them. 

CL-USER 5 > (my-if t (values 2 3) nil)
2

CL-USER 6 > (if t (values 2 3) nil)
2
3
From: David Steuber
Subject: Re: What's so special about IF?
Date: 
Message-ID: <87u0qfqt1r.fsf@david-steuber.com>
Clive Tong <··········@scientia.com> writes:

> David Steuber <·····@david-steuber.com> writes:
> 
> > (defmacro my-if (test then &optional (else nil))
> >   (let ((b (gensym)))
> >     `(let ((,b ,test))
> >        (or (and ,b ,then)
> >            (and (not ,b) ,else)))))
> > 
> 
> This macro doesn't deal properly with multiple values owing to the way
> OR deals with them. 
> 
> CL-USER 5 > (my-if t (values 2 3) nil)
> 2
> 
> CL-USER 6 > (if t (values 2 3) nil)
> 2
> 3

I didn't think of that test case.  I don't have a fix off the top of
my head for it.  Maybe that's what's special about IF.

On the face of it, it's not obvious why the VALUES don't propogate up
the stack frame:

CL-USER> (macroexpand '(my-if t (values 1 2) nil))
(LET ((#:G77 T)) (OR (AND #:G77 (VALUES 1 2)) (AND (NOT #:G77) NIL)))
T
CL-USER> (macroexpand '(or (and t (values 1 2))))
(IF T (AND (VALUES 1 2)))
T
CL-USER> (and (values 1 2))
1
2
CL-USER> (or (and t (values 1 2)))
1
2

-- 
An ideal world is left as an excercise to the reader.
   --- Paul Graham, On Lisp 8.1
From: Clive Tong
Subject: Re: What's so special about IF?
Date: 
Message-ID: <ullbq1zsk.fsf@scientia.com>
David Steuber <·····@david-steuber.com> writes:

> On the face of it, it's not obvious why the VALUES don't propogate up
> the stack frame:

It's due to the behaviour of OR with multiple values (which are only
returned from the last case of the OR) 

CL-USER 6 > (OR (AND t (VALUES 2 3)) (AND (NOT t) NIL))
2

CL-USER 7 > (OR (AND t (VALUES 2 3)) )
2
3
From: Jock Cooper
Subject: Re: What's so special about IF?
Date: 
Message-ID: <m3vfaslu5d.fsf@jcooper02.sagepub.com>
Clive Tong <··········@scientia.com> writes:

> David Steuber <·····@david-steuber.com> writes:
> 
> > On the face of it, it's not obvious why the VALUES don't propogate up
> > the stack frame:
> 
> It's due to the behaviour of OR with multiple values (which are only
> returned from the last case of the OR) 
> 
> CL-USER 6 > (OR (AND t (VALUES 2 3)) (AND (NOT t) NIL))
> 2
> 
> CL-USER 7 > (OR (AND t (VALUES 2 3)) )
> 2
> 3



(defmacro mv-or (&rest forms)
  (cond
    ((null forms) ())
    ((null (cdr forms)) (car forms))
    (t (let ((sym (gensym)))
	 `(let ((,sym (multiple-value-list ,(car forms))))
	   (if (car ,sym)
	       (values-list ,sym)
	       (mv-or ,@(cdr forms))))))))
From: Adam Warner
Subject: Re: What's so special about IF?
Date: 
Message-ID: <pan.2004.12.21.06.40.53.145588@consulting.net.nz>
Hi David Steuber,

> The CLHS states that IF is a Special Operator.  But what if there was
> no IF?  Don't ask my why I was thinking about this.  Just for fun, I
> decided to see if I could use the Macros AND and OR along with the
> function NOT to see if I could emulate IF:
> 
> (defmacro my-if (test then &optional (else nil))
>   (let ((b (gensym)))
>     `(let ((,b ,test))
>        (or (and ,b ,then)
>            (and (not ,b) ,else)))))

That's neat. Just note that IF is necessarily a special operator.
OR will be defined in terms of IF. (macroexpand '(or a b)) to see.

Regards,
Adam
From: David Steuber
Subject: Re: What's so special about IF?
Date: 
Message-ID: <87zn07qurw.fsf@david-steuber.com>
Adam Warner <······@consulting.net.nz> writes:

> That's neat. Just note that IF is necessarily a special operator.
> OR will be defined in terms of IF. (macroexpand '(or a b)) to see.

That's true.  The macro is quite clever also:

CL-USER> (macroexpand-1 '(or 1))
1
T
CL-USER> (macroexpand-1 '(or (> 4 (random 10)) "more" "less"))
(LET ((#:G75 (> 4 (RANDOM 10)))) (IF #:G75 #:G75 (IF (SETQ #:G75
"more") #:G75 "less")))
T
CL-USER> (macroexpand-1 '(and (> 4 (random 10)) "more" "less"))
(IF (> 4 (RANDOM 10)) (AND "more" "less"))
T

At the machine level, the clever bit is whatever instruction is used
for "Jump Zero" or "Jump Not Zero".  In the hardware, you are back to
AND, OR, and NOT.  Well almost.

IF is a good operator to place in the Special Operator class.

-- 
An ideal world is left as an excercise to the reader.
   --- Paul Graham, On Lisp 8.1
From: lin8080
Subject: Re: What's so special about IF?
Date: 
Message-ID: <41CA0E6A.9684FC00@freenet.de>
David Steuber schrieb:

> Some of the inspiration came from a digital logic course I once took
> which reduced everything in a computer to several fundamental gates.

> I know it's trivial, but I find this a rather eloquent answer to what
> makes Lisp special.

For more inspiration have a look at this (3.1)


...............(copy&paste).................
The fifth chapter of my book GENE EXPRESSION PROGRAMMING: MATHEMATICAL
MODELING BY AN ARTIFICIAL INTELLIGENCE is now available to browse online
at:

http://www.gene-expression-programming.com/gep/Books/index.asp

Chapter 5: DESIGN OF NEURAL NETWORKS
1. Genes with multiple domains for neural network simulation
2. Special search operators
2.1. Domain-specific transposition
2.2. Intragenic two-point recombination
2.3. Direct mutation of weights and thresholds
3. Solving problems with GEP neural networks
............
3.1. Neural network for the exclusive-or problem
............
3.2. Neural network for the 6-multiplexer
4. Evolutionary dynamics of GEP-nets

(Author at:)
GEP: Mathematical Modeling by an Artificial Intelligence
http://www.gene-expression-programming.com/gep/Books/index.asp
Modeling Software
http://www.gepsoft.com/gepsoft/
...................(end).............

Found in comp.ai.genetic

lin