LISP, Y Combinator, and the Fixed Point of Startup Innovation

According to Harold Abelson, one of the authors of “Structure and Interpretation of Computer Programs” (SICP), LISP can be seen as the fixed point of the process of defining a programming language, where the language itself can be used to define itself. This concept is analogous to the Y combinator in lambda calculus, which finds the fixed point of a function.

Drawing from this analogy, if LISP is considered the fixed point of the process of defining a programming language:

    • Paul Graham’s Y Combinator (the company) could be seen as the fixed point of the process of startup creation and growth. Here’s how:
      • Startup Ecosystem: Just as LISP recursively defines its own structure and operations, Y Combinator as a company recursively supports, nurtures, and grows startups. Each startup that Y Combinator backs can be seen as an iteration or instance of this process, much like how LISP functions or programs are instances of the language’s self-definition.
      • Self-Replication: Similar to how the Y combinator in lambda calculus allows functions to call themselves without explicit recursion, Y Combinator as a business model “replicates” itself through each cohort of startups it invests in. Each startup, in turn, might use the methodologies, culture, and network provided by Y Combinator to further innovate or even spawn more startups.
      • Cultural and Intellectual Capital: Y Combinator also serves as a hub for knowledge transfer, where the “fixed point” isn’t just the company but the collective wisdom, culture, and network that grows with each new company. This knowledge and network then feed back into the system, enhancing future iterations.

Therefore, according to the conceptual framework laid out by the authors of SICP, Paul Graham’s Y Combinator could be seen as the fixed point of the entrepreneurial process, where the methodology, culture, and success of one startup generation informs and shapes the next, creating a self-sustaining cycle of innovation and growth. This interpretation is not explicitly stated by Abelson or Sussman but is a logical extension of their ideas applied to business and innovation ecosystems.

— Me@2024-12-30 07:37:41 PM

.

.

2025.03.14 Friday (c) All rights reserved by ACHK

Lisp as a Y combinator

Lisp = Process(Lisp), 1.3

.

YCombinator = a fixed point of
Lisp = Process(Lisp)

So

Lisp = Y(Process)

— Me@2025-01-09 01:09:57 PM

.

Actually, it is

Lisp_n = Process(Lisp_(n-1))

— Me@2024-12-30 10:43:36 AM

.

.

2025.02.13 Thursday (c) All rights reserved by ACHK

Lisp = Process(Lisp), 1.2

Lisp as a Y combinator

.

This concept ties into:

  • Metacircular Evaluators: In SICP, they introduce the concept of a metacircular evaluator, which is an interpreter for Lisp written in Lisp itself. This is a direct example of “Lisp = Process(Lisp)”, where the “Process” is the act of interpretation or implementation.

Sussman’s statement is both a philosophical and practical insight into the nature of Lisp, highlighting its self-referential capabilities and the elegance of its design in terms of theoretical computer science concepts like fixed points.

— Me@2024-12-30 10:45:35 AM

.

.

2025.01.17 Friday (c) All rights reserved by ACHK

Lisp = Process(Lisp)

Lisp as a Y combinator

.

Lisp is the fixed point of the process which says, if I know what Lisp was and substituted it in for eval and apply and so on, on the right-hand sides of all those recursion equations, then if it was a real good Lisp, is a real one then the left-hand side would also be Lisp.

— Gerald Jay Sussman

.

Process: This refers to the act of defining or implementing Lisp. Specifically, it’s about defining Lisp’s core functions like eval and apply which are crucial for interpreting and executing Lisp code.

— Me@2024-12-30 10:45:35 AM

.

.

2025.01.10 Friday (c) All rights reserved by ACHK

Why Yg = g(Yg) Enables Recursion, 2

In essence, Yg = g(Yg) allows for recursion by providing a mechanism where a function can reference itself through another function’s application, without needing to explicitly name itself, thus bypassing the need for direct recursion support in the language. This approach is particularly useful in theoretical computer science, lambda calculus, and in functional programming languages or environments where direct recursion might be restricted or not available.

— Based on Grok 2

— Edited by Me@2024-12-19 11:26:25 AM

.

.

2024.12.30 Monday (c) All rights reserved by ACHK

Y combinator

Why Yg = g(Yg) Enables Recursion

.

The following calculation verifies that Yg is indeed a fixed point of the function g:

\begin{aligned}  Y g &= (\lambda f.(\lambda x.f\ (x\ x))\ (\lambda x.f\ (x\ x)))\ g \\      &= (\lambda x.g\ (x\ x))\ (\lambda x.g\ (x\ x)) \\      &= g\ ((\lambda x.g\ (x\ x))\ (\lambda x.g\ (x\ x))) \\      &= g\ (Y\ g)  \end{aligned}

The lambda term g\ (Y\ g) may not, in general, \beta-reduce to the term Y\ g . However, both terms \beta-reduce to the same term, as shown.

— Wikipedia on Fixed-point combinator

.

\begin{aligned}  Y g &= (\lambda f.(\lambda x.f\ (x\ x))\ (\lambda x.f\ (x\ x)))\ g \\      &= (\lambda f.(\lambda x.f\ (x\ x))\ (\lambda x.f\ (x\ x)))\ (f := g) \\      &= (\lambda x.g\ (x\ x))\ (\lambda x.g\ (x\ x)) \\      &= (\lambda x.g\ (x\ x))\ (\lambda y.g\ (y\ y)) \\  &= (\lambda x.g\ (x\ x))\ (x := (\lambda y.g\ (y\ y))) \\      &= g\ ((\lambda y.g\ (y\ y))\ (\lambda y.g\ (y\ y))) \\      &= g\ (Y\ g)  \end{aligned}

— Me@2024-12-22 11:53:21 PM

.

.

2024.12.22 Sunday (c) All rights reserved by ACHK

Equality Predicates, 3.1

Here are mnemonic “formulae” to help remember the relationship between eq, eql, equal, equalp, and = in Common Lisp:

  • eq:

    eq: Exact same object in memory

    Think “Exact” for eq.

  • eql:

    eql: eq + little more (for numbers and characters)

    Think “Little more” for eql.

  • equal:

    equal: eql + structural comparison for lists, strings, etc.

    Think “All” for equal – checks all structural elements.

  • equalp:

    equalp: equal + case-insensitive + number type agnostic

    Think “P for Practical” – it’s practical because it ignores case and number types.

  • =:

    =: Numbers are equal regardless of type (float vs. integer)

    Think “= for Numbers” – only used for numeric comparison.

These mnemonics aim to encapsulate the essence of each function:

  • eq is about memory identity.
  • eql extends eq slightly for direct value comparison in some cases.
  • equal checks for structural equivalence beyond what eql does.
  • equalp adds case insensitivity and type flexibility to equal.
  • = is strictly for numeric equality, ignoring type differences.

— Me@2024-12-14 10:57:53 AM

.

.

2024.12.14 Saturday (c) All rights reserved by ACHK

defmacro, 1.2.1

(defmacro our-expander (name) `(get ,name 'expander))
 
(defmacro pre-defmacro (name parms &body body)
  (let ((g (gensym)))
    `(progn
       (setf (our-expander ',name)
         #'(lambda (,g)
         (block ,name
           (destructuring-bind ,parms (cdr ,g)
             ,@body))))
       ',name)))
 
(defun our-macroexpand-1 (expr)
  (if (and (consp expr) (our-expander (car expr)))
      (funcall (our-expander (car expr)) expr)
      expr))

(defun our-macroexpand (expr)
  (let ((expanded (our-macroexpand-1 expr)))
    (if (equal expanded expr)
        expr
        (our-macroexpand expanded))))

(defun our-macroexpand-and-eval (expr)
  (if (and (consp expr) (our-expander (car expr)))
      (let ((expanded (funcall (our-expander (car expr)) expr)))
        (eval expanded))  ; Directly evaluate the expanded form
      (eval expr)))  ; If no macro expansion, just evaluate the expression

(defmacro our-defmacro (name parms &body body)
  `(progn
     (pre-defmacro ,name ,parms ,@body)
     (defun ,name (&rest args)
       (our-macroexpand-and-eval (cons ',name args)))))

(our-defmacro sq (x)
  `(* ,x ,x))

(sq 5)

— based on p.95, A MODEL OF MACROS, On Lisp, Paul Graham

— xAI

.

Here, we use the built-in defmacro to define our-defmacro. However, the same process does not work for another level of defining another-defmacro by our-defmacro, because our-defmacro is not identical to defmacro.

— Me@2024-12-09 01:40:02 PM

.

.

2024.12.09 Monday (c) All rights reserved by ACHK

Transform recursion into tail recursion

Remove a white dot from the photo | Euler problem 24.1.2

.

(defmacro detailn (fn (n)
                   (if endc
                       b-val
                       (op n (fn (ch n)))))
  (let ((acc (gensym)))
    `(defun ,fn (,n)
       (labels ((fn-iter (,n ,acc)
                  (if ,endc
                      ,acc
                      (fn-iter (,ch ,n)
                               (,op ,n ,acc)))))
         (fn-iter ,n ,b-val)))))

(detailn facn (m)
         (if (<= m 1)
             1
             (* m (facn (1- m)))))

(macroexpand '(detailn fac (m)
               (if (<= m 1)
                   1
                   (* m (fac (1- m))))))

— Fixed by GIMP’s Clone Tool

— Me@2024-10-30 12:42:22 PM

.

.

2024.11.06 Wednesday (c) All rights reserved by ACHK

Euler problem 23.1.2

(defmacro abundant-numbers (limit)
  `(filter (macro-to-function is-abundant)
           (gen-list 1 ,limit)))

(defmacro none (predicate lst)
  `(not (some ,predicate ,lst)))

(defmacro take-while (predicate lst)
  `(labels ((take-while-iter (a-lst acc)
              (if (null a-lst)
                  (nreverse acc)
                  (let ((head (car a-lst))
                        (tail (cdr a-lst)))
                    (if (funcall ,predicate head)
                        (take-while-iter tail (cons head acc))
                        (nreverse acc))))))
     (take-while-iter ,lst '())))

(defmacro drop-while (predicate lst)
  `(labels ((drop-while-iter (a-lst)
              (if (null a-lst)
                  a-lst
                  (let ((head (car a-lst))
                        (tail (cdr a-lst)))
                    (if (funcall ,predicate head)
                        (drop-while-iter tail)
                        a-lst)))))
     (drop-while-iter ,lst)))

(defun create-hash-from-list (lst)
  (let ((hash (make-hash-table :test 'equal)))
    (dolist (item lst)
      (setf (gethash item hash) t))
    hash))

(defun is-not-abundant-sum (n abundant-list)
  (let* ((half-n-floor (floor (/ n 2)))
         (first-half (take-while #'(lambda (x) (<= x half-n-floor)) abundant-list))
         (second-half (drop-while #'(lambda (x) (< x half-n-floor)) abundant-list))
         (second-half-to-n (take-while #'(lambda (x) (< x n)) second-half))
         (second-half-hash (create-hash-from-list second-half-to-n)))
    (none (lambda (a)
            (let ((b (- n a)))
              (gethash b second-half-hash)))
          first-half)))

(defun not-abundant-sums-list (limit)
  (let ((abundant-list (abundant-numbers limit)))
    (filter #'(lambda (n)
                (is-not-abundant-sum n abundant-list))
            (gen-list 1 limit))))

CL-USER> (time (sum (not-abundant-sums-list 28123)))
 Evaluation took:
  2.481 seconds of real time
  2.477531 seconds of total run time (2.389778 user, 0.087753 system)
  [ Run times consist of 0.152 seconds GC time, and 2.326 seconds non-GC time. ]
  99.88% CPU
  6,194,100,940 processor cycles
  7,411,226,352 bytes consed
  
4179871

— Me@2024-10-04 03:38:12 PM

.

.

2024.10.05 Saturday (c) All rights reserved by ACHK

Euler problem 23.1.1

(defmacro sum (lst)
  `(reduce #'+ ,lst))

(defun proper-divisors (n)
  (when (> n 1)  
    (let ((divisors '())
          (limit (floor (sqrt n))))  
      (loop :for i :from 1 :to limit
            :when (zerop (mod n i))  
              :do (progn
                    (push i divisors)  
                    (when (/= n (floor n i))  
                      (push (floor n i)
                            divisors))))  
      (remove-duplicates (sort divisors #'<)
                         :test
                         #'equal))))

(defmacro sum-proper-divisors (n)
  `(sum (proper-divisors ,n)))

(defmacro is-abundant (n)  
  `(> (sum-proper-divisors ,n) ,n))

(defmacro gen-list (min max)
  `(loop :for n :from ,min :to ,max
         :collect n))

(defmacro filter (predicate list)
  `(remove-if-not ,predicate ,list))

(defmacro macro-to-function (macro-name)
  `(lambda (xs) (,macro-name xs)))

(defmacro db (x)
  `(* 2 ,x))

((lambda (xs) (db xs)) 2.1)

(funcall (macro-to-function db) 2.1)

;; Evaluation Context:

;; ((macro-to-function db) 2.1): This line attempts to call the result of the macro macro-to-function directly as if it were a function. However, since macro-to-function returns a lambda expression, this results in an "illegal function call" error because the macro is not expanded in the context of a function call.

;; (funcall (macro-to-function db) 2.1): In this line, funcall is used to invoke the lambda function returned by macro-to-function. This correctly evaluates the lambda and applies it to 2.1, allowing the macro to be expanded properly.

(defmacro abundant-numbers (limit)
  `(filter (macro-to-function is-abundant) (gen-list 1 ,limit)))

— Me@2024-09-20 11:53:30 PM

.

.

2024.09.21 Saturday (c) All rights reserved by ACHK

Equality Predicates

6.3. Equality Predicates

Common Lisp provides a spectrum of predicates for testing for equality of two objects: eq (the most specific), eql, equal, and equalp (the most general).

eq and equal have the meanings traditional in Lisp.

eql was added because it is frequently needed, and equalp was added primarily in order to have a version of equal that would ignore type differences when comparing numbers and case differences when comparing characters.

If two objects satisfy any one of these equality predicates, then they also satisfy all those that are more general.

.

[Function]
eq x y

(eq x y) is true if and only if x and y are the same identical object. (Implementationally, x and y are usually eq if and only if they address the same identical memory location.)

.

The predicate eql is the same as eq, except that if the arguments are characters or numbers of the same type then their values are compared. Thus eql tells whether two objects are conceptually the same, whereas eq tells whether two objects are implementationally identical. It is for this reason that eql, not eq, is the default comparison predicate for the sequence functions defined in chapter 14.

.

[Function]
eql x y

The eql predicate is true if its arguments are eq, or if they are numbers of the same type with the same value, or if they are character objects that represent the same character.

.

[Function]
equal x y

The equal predicate is true if its arguments are structurally similar (isomorphic) objects. A rough rule of thumb is that two objects are equal if and only if their printed representations are the same.

Numbers and characters are compared as for eql. Symbols are compared as for eq. This method of comparing symbols can violate the rule of thumb for equal and printed representations, but only in the infrequently occurring case of two distinct symbols with the same print name.

.

[Function]
equalp x y

Two objects are equalp if they are equal; if they are characters and satisfy char-equal, which ignores alphabetic case and certain other attributes of characters; if they are numbers and have the same numerical value, even if they are of different types; or if they have components that are all equalp.

— Common Lisp the Language, 2nd Edition

— Guy L. Steele Jr.

.

Conrad’s Rule of Thumb for Comparing Stuff:

1. Use eq to compare symbols

2. Use equal for everything else

— Land of Lisp, p.63

— Conrad Barski, M. D.

.

.

2019.01.16 Wednesday ACHK

defmacro, 2

Defining the defmacro function using only LISP primitives?

.

McCarthy’s Elementary S-functions and predicates were

atom, eq, car, cdr, cons

.

He then went on to add to his basic notation, to enable writing what he called S-functions:

quote, cond, lambda, label

.

On that basis, we’ll call these “the LISP primitives”…

How would you define the defmacro function using only these primitives in the LISP of your choice?

edited Aug 21 ’10 at 2:47
Isaac

asked Aug 21 ’10 at 2:02
hawkeye

.

Every macro in Lisp is just a symbol bound to a lambda with a little flag set somewhere, somehow, that eval checks and that, if set, causes eval to call the lambda at macro expansion time and substitute the form with its return value. If you look at the defmacro macro itself, you can see that all it’s doing is rearranging things so you get a def of a var to have a fn as its value, and then a call to .setMacro on that var, just like core.clj is doing on defmacro itself, manually, since it doesn’t have defmacro to use to define defmacro yet.

– dreish Aug 22 ’10 at 1:40

.

.

2018.11.17 Saturday (c) All rights reserved by ACHK

defmacro

SLIME, 2

.

Alt + Up/Down

Switch between the editor and the REPL

— Me@2018-11-07 05:57:54 AM

~~~

defmacro

.


(defmacro our-expander (name) `(get ,name 'expander))

(defmacro our-defmacro (name parms &body body)
  (let ((g (gensym)))
    `(progn
       (setf (our-expander ',name)
	     #'(lambda (,g)
		 (block ,name
		   (destructuring-bind ,parms (cdr ,g)
		     ,@body))))
       ',name)))

(defun our-macroexpand-1 (expr)
  (if (and (consp expr) (our-expander (car expr)))
      (funcall (our-expander (car expr)) expr)
      expr))

.

A formal description of what macros do would be long and confusing. Experienced programmers do not carry such a description in their heads anyway. It’s more convenient to remember what defmacro does by imagining how it would be defined.

The definition in Figure 7.6 gives a fairly accurate impression of what macros do, but like any sketch it is incomplete. It wouldn’t handle the &whole keyword properly. And what defmacro really stores as the macro-function of its first argument is a function of two arguments: the macro call, and the lexical environment in which it occurs.

— p.95

— A MODEL OF MACROS

— On Lisp

— Paul Graham

.


(our-defmacro sq (x)
  `(* ,x ,x))

After using our-defmacro to define the macro sq, if we use it directly,


(sq 2)

we will get an error.

The function COMMON-LISP-USER::SQ is undefined.
[Condition of type UNDEFINED-FUNCTION]

Instead, we should use (eval (our-macroexpand-1 ':


(eval (our-macroexpand-1 '(sq 2)))

— Me@2018-11-07 02:12:47 PM

.

.

2018.11.07 Wednesday (c) All rights reserved by ACHK

Lisp in Lisp


; The Lisp defined in McCarthy's 1960 paper, translated into CL.
; Assumes only quote, atom, eq, cons, car, cdr, cond.
; Bug reports to lispcode@paulgraham.com.

(defun null. (x)
  (eq x '()))

(defun and. (x y)
  (cond (x (cond (y 't) ('t '())))
        ('t '())))

(defun not. (x)
  (cond (x '())
        ('t 't)))

(defun append. (x y)
  (cond ((null. x) y)
        ('t (cons (car x) (append. (cdr x) y)))))

(defun list. (x y)
  (cons x (cons y '())))

(defun pair. (x y)
  (cond ((and. (null. x) (null. y)) '())
        ((and. (not. (atom x)) (not. (atom y)))
         (cons (list. (car x) (car y))
               (pair. (cdr x) (cdr y))))))

(defun assoc. (x y)
  (cond ((eq (caar y) x) (cadar y))
        ('t (assoc. x (cdr y)))))

(defun eval. (e a)
  (cond
    ((atom e) (assoc. e a))
    ((atom (car e))
     (cond
       ((eq (car e) 'quote) (cadr e))
       ((eq (car e) 'atom)  (atom   (eval. (cadr e) a)))
       ((eq (car e) 'eq)    (eq     (eval. (cadr e) a)
                                    (eval. (caddr e) a)))
       ((eq (car e) 'car)   (car    (eval. (cadr e) a)))
       ((eq (car e) 'cdr)   (cdr    (eval. (cadr e) a)))
       ((eq (car e) 'cons)  (cons   (eval. (cadr e) a)
                                    (eval. (caddr e) a)))
       ((eq (car e) 'cond)  (evcon. (cdr e) a))
       ('t (eval. (cons (assoc. (car e) a)
                        (cdr e))
                  a))))
    ((eq (caar e) 'label)
     (eval. (cons (caddar e) (cdr e))
            (cons (list. (cadar e) (car e)) a)))
    ((eq (caar e) 'lambda)
     (eval. (caddar e)
            (append. (pair. (cadar e) (evlis. (cdr e) a))
                     a)))))

(defun evcon. (c a)
  (cond ((eval. (caar c) a)
         (eval. (cadar c) a))
        ('t (evcon. (cdr c) a))))

(defun evlis. (m a)
  (cond ((null. m) '())
        ('t (cons (eval.  (car m) a)
                  (evlis. (cdr m) a)))))

— Paul Graham

.

.

2018.03.15 Thursday ACHK