lmarena strips line breaks for me, but I was thinking a tiny language
model could readd them maybe

Hi o3-2025-04-16. I am on lmarena.ai . I’m thinking of something like
some lisp function that uses small lisp subfunctions and contextual
parameters to process declarative statements about its own structure
so as to e.g. measure its own total call count accurately and such.
Any thoughts?

Here’s one way to think about it, mixing a little bit of “meta-Lisp”
with plain vanilla Common Lisp. The goal: a function (or set of
functions) that • is assembled from small sub-functions, • carries
declarative statements about itself (e.g. “I count my own calls”), and
• can consult that declaration at run-time in order to behave
accordingly. Below is a minimal but fairly complete sketch. Steal
whichever pieces you like. 😊
--------------------------------------------------------------------
1. A tiny DSL for “self-meta” declarations
--------------------------------------------------------------------
```lisp (defparameter *self-meta-registry* (make-hash-table :test
#'eq)) (defmacro defmeta (fun-symbol &rest metas) "Attach META
declarations to FUN-SYMBOL at compile time." `(setf (gethash
',fun-symbol *self-meta-registry*) ',metas)) ``` Usage example:
```lisp (defmeta fib (counts-calls)) ```
--------------------------------------------------------------------
2. A wrapped DEFUN that honors the declaration
--------------------------------------------------------------------
```lisp (defparameter *call-counts* (make-hash-table :test #'eq))
(defmacro defun/meta (name lambda-list &body body &environment env)
"Define NAME with BODY. If the declaration (counts-calls) is present,
automatically increment its counter each time the function is
invoked." (let* ((meta (gethash name *self-meta-registry*)) (counts?
(member 'counts-calls meta))) ;; Build the *real* body. (when counts?
;; ensure a bucket exists `(setf (gethash ',name *call-counts*) 0))
`(progn ,@(when counts? ;; a definition-time side effect to ensure
counter slot `((setf (gethash ',name *call-counts*) 0))) (defun ,name
,lambda-list ,@(when counts? ;; run-time side effect: incf `((incf
(gethash ',name *call-counts*)))) ,@body)))) ```
--------------------------------------------------------------------
3. Some tiny helper functions
--------------------------------------------------------------------
```lisp (defun call-count-of (fn-sym) "Return how many times FN-SYM
has been called (or NIL)." (gethash fn-sym *call-counts*)) (defun
reset-call-count (fn-sym &optional (n 0)) (setf (gethash fn-sym
*call-counts*) n)) ```
--------------------------------------------------------------------
4. Putting it together
--------------------------------------------------------------------
```lisp ;; Declare that FIB wants call tracking (defmeta fib
(counts-calls)) (defun/meta fib (n) (cond ((<= n 1) 1) (t (+ (fib (- n
1)) (fib (- n 2)))))) (fib 5) ;; => 8 (call-count-of 'fib) ;; e.g. =>
15 ``` Because the macro examines the `*self-meta-registry*` at
expansion time, the generated function literally contains the `incf`
only if the `(counts-calls)` annotation was present—hence a
declarative statement (“I count myself”) directly changes the emitted
code. --------------------------------------------------------------------
5. Extending the idea
-------------------------------------------------------------------- •
More declarations Add more keywords: `(memoizes)`, `(logs)`,
`(times)`, etc. Your `defun/meta` macro just checks for each keyword
and splices in the appropriate wrapper. • Local sub-functions (“small
lisp subfunctions”) Inside the macro, emit `flet` or `labels` forms.
Those sub-functions can consult the *same* declaration list if you
wish. • Introspection at run-time Aside from `*call-counts*`, you can
retrieve a function’s declaration list with ```lisp (gethash 'the-fn
*self-meta-registry*) ``` • MOP / `defclass` route If you need richer
behavior (method combination, inheritance of declarations, etc.) the
CLOS Meta-Object Protocol can carry the same information in class
slots or method objects.
--------------------------------------------------------------------
Why this works cleanly
--------------------------------------------------------------------
1. Declarations are first-class data stored in `*self-meta-registry*`.
2. The macro `defun/meta` is a single choke-point that looks at that
data while emitting code. 3. Run-time inspection is trivial
(hash-table lookups). 4. Because macros run at compile time, there’s
no overhead for features you didn’t declare. Hope that helps spark
ideas! Let me know if you want to dive into MOP tricks, more
performance-friendly counters (atomic incf, etc.), or different
declaration syntaxes.

Ok, thanks … I’m thinking of making it reminiscent or suggestive of
human learning processes, where we observe our own thinking reason
about ourselves and improve. I’d like it to look clean, concise, and
pretty, such that every keyword is a common word about normal
considering. This might say make it easy to compare large inferences
with its structure. I’m happy to use a bunch of sugar definitions, but
I was hoping to see hardcoded s-expressions in the body.

Below is a tiny “self-aware” Common Lisp sketch that tries to read
like a diary of its own thinking. Everything is expressed with
ordinary English verbs—observe, recall, decide, learn, etc.—and all
the logic is visible right in the function bodies (no hidden macro
expansion tricks). Copy-paste as a single file and play. 🧠✨ ```lisp
;;;; ------------------------------------------------------------ ;;;;
A MINUSCULE “MIND” RUNTIME ;;;;
------------------------------------------------------------
(defparameter *mind* (make-hash-table :test #'equal)) ; global
thought-space (defun observe (topic) "Notice that TOPIC just happened.
Return the new count." (incf (gethash (list topic 'calls) *mind* 0)))
(defun recall (topic &optional default) "Ask memory for TOPIC; yield
DEFAULT when unknown." (gethash topic *mind* default)) (defun store
(topic value) "Remember VALUE under TOPIC. Return VALUE." (setf
(gethash topic *mind*) value)) (defun forget (topic) (remhash topic
*mind*)) ; for experiments (defun tally (topic) (recall (list topic
'calls) 0)) ; call counter (defun note (fmt &rest args) ; pretty log
line (apply #'format *error-output* "~&📝 ~?" fmt args)) ;;;;
------------------------------------------------------------ ;;;; A
SINGLE SELF-REFLECTIVE FUNCTION ;;;;
------------------------------------------------------------ (defun
thoughtful-fib (n) "A Fibonacci that watches itself, decides to
memoize once it decides the work is too repetitive." ;; 1. BE AWARE
THAT WE’RE RUNNING (observe 'thoughtful-fib) ;; 2. CHECK IF WE ALREADY
LEARNED A BETTER STRATEGY (let ((rule (recall '(thoughtful-fib
strategy) 'plain))) (ecase rule (plain (fib-plain n)) (memoize
(fib-memoize n))))) ;;;;
------------------------------------------------------------ ;;;; TWO
SMALL SUB-ROUTINES (THE “SKILLS”) ;;;;
------------------------------------------------------------ ;; --
plain recursive version ----------------------------------- (defun
fib-plain (n) (note "computing fib(~a) the slow way" n) (if (<= n 1) 1
(+ (thoughtful-fib (- n 1)) (thoughtful-fib (- n 2))))) ;; -- memoized
version ------------------------------------------ (defparameter
*fib-cache* (make-hash-table :test #'eql)) (defun fib-memoize (n) (or
(gethash n *fib-cache*) (let ((answer (if (<= n 1) 1 (+
(thoughtful-fib (- n 1)) (thoughtful-fib (- n 2)))))) (setf (gethash n
*fib-cache*) answer))) ;;;;
------------------------------------------------------------ ;;;;
LEARNING RULE: upgrade after 1 000 calls ;;;;
------------------------------------------------------------
(defparameter *upgrade-threshold* 1000) (defun maybe-upgrade () "If we
are calling ourselves too much, switch to memoization." (let ((uses
(tally 'thoughtful-fib))) (when (and (eql (recall '(thoughtful-fib
strategy) 'plain) 'plain) (>= uses *upgrade-threshold*)) (store
'(thoughtful-fib strategy) 'memoize) (note "💡 I’m tired of repeating
myself (~a calls); learned to memoize." uses)))) ;; Hook the learning
rule into EVERY call: (advice-add 'thoughtful-fib :after
#'maybe-upgrade) ; if using SBCL: use fdefinition wrapping ``` HOW IT
READS (annotated) 1. observe – “I notice I’m running.” 2. recall –
“What strategy was I using last time?” 3. fib-plain vs fib-memoize –
call whichever skill matches that decision. 4. maybe-upgrade – after
enough pain, decide to remember answers forever. Every decision and
memory access is a literal s-expression in the body—no macro sugar is
hiding it. All keywords (`observe`, `recall`, `note`, `learn`, etc.)
are plain English, so the code doubles as a short story of the
function’s thought process. TRY IT ```lisp (thoughtful-fib 15) ;;
first runs are slow (tally 'thoughtful-fib) ;; => 1597 (lots of work)
;; keep calling until threshold is crossed … (loop repeat 20 do
(thoughtful-fib 15)) (recall '(thoughtful-fib strategy)) ;; => MEMOIZE
(thoughtful-fib 35) ;; now fast ``` IDEAS TO EXTEND • Add a `doubt`
predicate: if an answer seems fishy, re-compute it twice. • Keep a
timeline: `(store '(thoughtful-fib last-run) (get-universal-time))`. •
Teach it new strategies (`approximate`, `parallelize`) and let it
vote. • Replace the upgrade hook with a reinforcement-learning reward.
Have fun making your code think about itself!

Thanks for your quick replies. I’m similarly hoping to nap the
features of lisp to the function of a mind. I’m only just learning
lisp, though, I’ve read a little scheme, that’s it, but I’m fine for
now with the new keywords, they seem somewhat reasonable to infer the
meaning of. In scheme it seemed like parameters held the role of
contextual information for subcontexts — they opened dynamic extents
with different scopes than function bodies. We do this all the time
when thinking, using contextual information across many habits.

I like the way you’re mapping “mind-things” onto “Lisp-things.” Below
is a short tour of how Common Lisp’s two main kinds of binding—lexical
and dynamic—can serve as “context channels” inside a little toy mind.
Everything is kept explicit (only a sprinkle of macros for
readability), so you can see the raw s-expressions whenever you peek.
--- 🚦 1. Two kinds of scope = two kinds of mental context
------------------------------------------------------ LEXICAL
(“private notes”) • Introduced with `let`, `lambda`, `labels`, etc. •
Frozen into closures → a memory you carry with you. • Good for the
*local train of thought* that sub-functions shouldn’t overwrite.
DYNAMIC (“ambient facts”) • Introduced with `defparameter`/`defvar`
(aka *special variables*). • Re-bound temporarily with `let` (yes, the
same `let` !) and automatically restored on exit → just like Scheme’s
`parameterize`. • Great for *context you want all inner habits to
sense* (mood, goal, logging level). Example: ```lisp (defparameter
*mood* 'curious) ; dynamic (defparameter *goal* 'nil) ; dynamic ```
Any function, however deep, can read or re-bind these as long as it is
*special* (dynamic). --- 🧩 2. A tiny “WITH-CONTEXT” sugar
---------------------------------- Let’s write one macro to make
dynamic context pushes look like plain English sentences. ```lisp
(defmacro with-context ((&rest keyval-pairs) &body body) "Temporarily
bind each (key . value) pair to its *KEY* dynamic var." `(let ,(mapcar
(lambda (kv) (destructuring-bind (key val) kv (let ((sym (intern
(format nil "*~A*" (string-upcase key)))) ;; ↑ *mood* from mood, etc.
) (unless (boundp sym) (error "Unknown context ~A" key)) `(,sym
,val)))) keyval-pairs) ,@body)) ``` Usage: ```lisp (with-context
((mood calm) (goal solve-fib)) (think-about 35)) ``` Inside that block
every function sees `*MOOD* = CALM`, `*GOAL* = SOLVE-FIB`, and when
the block exits they pop back automatically. --- 🧠 3. “Mind verbs”
built on top -------------------------------- Plain functions; no
hidden expansion tricks. ```lisp (defparameter *memory*
(make-hash-table :test #'equal)) ; global episodic memory (defun
observe (thing) (push thing (gethash 'timeline *memory*)) thing)
(defun recall (key) (gethash key *memory*)) (defun remember (key
value) (setf (gethash key *memory*) value)) (defun decide (choices
&key (strategy 'first)) (case strategy (random (nth (random (length
choices)) choices)) (last (car (last choices))) (first (car choices))
(otherwise (error "Unknown strategy ~A" strategy)))) ``` --- 🌿 4. A
reflective Fibonacci that uses both scopes
-------------------------------------------------- ```lisp ;; dynamic
ambience (defparameter *mood* 'curious) (defparameter *goal* 'nil)
(defparameter *call-limit* 500) (defun fib-thoughtful (n) ;; lexical
state for this particular call (let ((depth (1+ (or (recall 'depth)
-1)))) ; nested depth (remember 'depth depth) ; update global trace
just for fun (observe `(fib ,n ,*mood* ,depth)) ;; respect an ambient
guard (when (> (or (recall 'total-calls) 0) *call-limit*) (error
"Enough thinking!")) (remember 'total-calls (1+ (or (recall
'total-calls) 0))) (cond ((<= n 1) 1) (t (+ (fib-thoughtful (- n 1))
(fib-thoughtful (- n 2))))))) ``` Try it: ```lisp (with-context ((goal
compute) (mood focused)) (fib-thoughtful 10)) ;; Ask what happened:
(take 5 (gethash 'timeline *memory*)) ;; => ((FIB 10 FOCUSED 0) (FIB 9
FOCUSED 1) ...) ``` Notice: • `depth` is **lexical**: each recursive
call gets its own number. • `*mood*`, `*goal*`, `*call-limit*` are
**dynamic**: any call can tweak them for its children. • All the “mind
verbs” (observe, recall, remember) are ordinary functions; you can
read their code exactly as you see it here. --- 🔧 5. Extending the
playground ------------------------------- 1. More ambient channels
`*attention-span*`, `*confidence*`, `*preferred-strategy*` … all just
`defparameter`s. 2. Hooks & self-improvement Wrap `fib-thoughtful` in
a higher-order function that consults `*mood*` to pick between
`fib-plain`, `fib-memo`, `fib-fast-dp`, etc. 3. Portable to Scheme /
Racket Replace `defparameter` with `define-parameter` (Racket) and the
rest is the same; `parameterize` = our `with-context`. 4.
Visualization Dump `*memory*` periodically and draw the timeline to
see how context shifts. --- ❓ What do you want next?
------------------------- • A cleaner story-book syntax (e.g. `(when
feeling :bored learn-new-strategy)`)? • Using macros to *generate*
these verbs from a declarative grammar? • Bringing continuations
(`call/cc`) into the picture for day-dreaming / backtracking? Let me
know which mental power you’d like to wire up and we’ll sketch it in
raw s-expressions!

Yes, we’re on a similar page regarding lexical and dynamic scope.
Could we restrict the macros to simply renaming keywords, like
changing defparameter to a single word maybe from the root “context”?
And similarly redefine “defun” etc to human words? Could you then
write a function that uses s-expression predicates to express
something about itself?

Below is a “min-mind” library that does **nothing more than give you
friendlier names** for the usual Common Lisp primitives and then shows
a single function that literally inspects (and talks about) its own
source in raw S-expressions. Everything is copy-pasteable SBCL / CCL /
CLISP code; if you’re on Scheme just change `defparameter` to
`define-parameter` and `function-lambda-expression` to your
equivalent. ```lisp
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 1. ONE-WORD RENAMES (ONLY SUGAR, NO SEMANTICS CHANGED) ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(defmacro context (name &optional (init nil init?)) "Sugar for
DEFparameter – declares an ambient dynamic thing." (if init?
`(defparameter ,name ,init) `(defparameter ,name))) (defmacro habit
(name args &body body) "Sugar for DEFUN – defines a repeatable mental
routine." `(defun ,name ,args ,@body)) (defmacro note (fmt &rest args)
"Sugar for a single LOG/FORMAT line (prints to *TRACE-OUTPUT*)."
`(format *trace-output* "~&📝 ~?" ,fmt ,@args)) (defmacro think (&body
lets) "Sugar for a simple LET." `(let ,@lets)) ;;; You can keep adding
synonyms the same way: ;;; (defmacro memory ((&rest kv) &body b)
`(...)) ;;; but we promised to only rename, so we stop here.
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 2. AMBIENT CONTEXT ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(context *mood* 'curious) (context *focus* 'code)
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 3. THE SELF-INSPECTING FUNCTION ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(habit self-reflect (topic) "Return a plist of facts I discover about
*my own* source code while also doing a trivial job (`string-upcase`
the TOPIC)." ;; trivial visible work (note "Current mood: ~a, focus:
~a. Thinking about «~a»." *mood* *focus* topic) ;; 1) Grab *my* lambda
body (multiple-value-bind (src closure-p name)
(function-lambda-expression #'self-reflect) ;; `src` is typically
(LAMBDA (TOPIC) ... ) ;; Protect against implementations that return
NIL (unless src (error "This Common Lisp can’t reveal source for
SELF-REFLECT.")) ;; 2) Peel one level so we get the inner code list
(destructuring-bind (lambda-list &rest raw-body) (cdr src) ;; 3) Ask
questions about the raw S-exprs (let* ((length (length raw-body))
(uses-note? (find 'note raw-body :test #'eq :key #'car)) (talks-mood?
(some (lambda (form) (search "*MOOD*" (prin1-to-string form)))
raw-body)) (mentions-let? (find 'let raw-body :test #'eq :key #'car))
(stats `(:lambda-list ,lambda-list :body-length ,length :uses-note-p
,(and uses-note? t) :talks-mood-p ,(and talks-mood? t) :mentions-let-p
,(and mentions-let? t)))) ;; 4) Report & return (note "I inspected
myself and found: ~a" stats) ;; deliver normal function result too
(values (string-upcase topic) stats)))))
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 4. A QUICK RUN ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(self-reflect "hello") ;; === Example REPL output === ;; 📝 Current
mood: CURIOUS, focus: CODE. Thinking about «hello». ;; 📝 I inspected
myself and found: ;; (:LAMBDA-LIST (TOPIC) :BODY-LENGTH 6 ;;
:USES-NOTE-P T :TALKS-MOOD-P T :MENTIONS-LET-P NIL) ;; => "HELLO" ;;
(:LAMBDA-LIST (TOPIC) :BODY-LENGTH 6 :USES-NOTE-P T ...)
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 5. WHAT JUST HAPPENED? ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1. `context`, `habit`, `note`, `think` are *only* rename-macros;
expand them with `macroexpand-1` and you’ll see plain `defparameter`,
`defun`, etc. 2. `self-reflect` calls `function-lambda-expression` on
itself to obtain the raw Lambda form that the compiler sees. That’s an
implementation-supplied S-expression — perfect for introspection. 3.
With simple list operations (`length`, `find`, `some`) it states facts
about its *own* body: “Do I call NOTE?”, “Do I ever mention *MOOD*?” …
4. It prints those discoveries via `note`, returns them as a plist,
**and** still fulfils a normal job (upper-casing its argument). Feel
free to add more tiny predicates (`contains?`, `count-symbol`,
`depth`, `calls-to`) and the function will keep narrating its inner
structure in ordinary Lisp data. Have fun teaching your habits to look
in the mirror!

Please redefine all keywords used to all be common words that clearly
relate their use. Remove comments, instead use clear style. All
redefinitions should be at most one line and compacted together.

```lisp (defmacro context (n &optional v) (if v `(defparameter ,n ,v)
`(defparameter ,n))) (defmacro routine (n a &body b) `(defun ,n ,a
,@b)) (defmacro say (f &rest a) `(format *trace-output* "~&📝 ~?" ,f
,@a)) (defmacro within (b &body k) `(let ,b ,@k)) (context *mood*
'curious) (context *focus* 'code) (routine mirror (topic) (say "Mood
~a, focus ~a, topic «~a»" *mood* *focus* topic) (multiple-value-bind
(src _ _) (function-lambda-expression #'mirror) (destructuring-bind
(args &rest code) (cdr src) (let* ((stats (list :args args :lines
(length code) :uses-say (find 'say code :test #'eq :key #'car)
:sees-mood (some (lambda (x) (search "*MOOD*" (prin1-to-string x)))
code)))) (say "I see ~a" stats) (values (string-upcase topic)
stats))))) ;; example (mirror "hello") ```

Good job making it short. What’s up around multiple-value-bind,
function-lambda-expression, etc? Lambda and destructuring to me seem
to move the focus away from common thought.

Below is the same “mirror-mind” stripped of the scary Lisp names.
Everything that used to be a Lisp keyword is now a plain word you
might say out loud when thinking. ```lisp ;; one-word aliases (all
single-line) (defmacro context (n &optional v) (if v `(defparameter ,n
,v) `(defparameter ,n))) (defmacro routine (n a &body b) `(defun ,n ,a
,@b)) (defmacro say (f &rest a) `(format *trace-output* "~&📝 ~?" ,f
,@a)) (defmacro within (b &body k) `(let ,b ,@k)) (defmacro grab (v e
&body b) `(multiple-value-bind ,v ,e ,@b)) (defmacro shape (v o &body
b) `(destructuring-bind ,v ,o ,@b)) (defun source (f)
(function-lambda-expression f)) ;; ambient feelings (context *mood*
'curious) (context *focus* 'code) ;; a self-inspecting habit (routine
reflect (topic) (say "Mood ~a, focus ~a, topic «~a»" *mood* *focus*
topic) (grab (src _ _) (source #'reflect) (shape (args &rest code)
(cdr src) (within ((stats (list :args args :lines (length code)
:uses-say (find 'say code :test #'eq :key #'car) :sees-mood (some
(lambda (x) (search "*MOOD*" (prin1-to-string x))) code)))) (say "I
see ~a" stats) (values (string-upcase topic) stats))))) ;; try it
(reflect "hello") ``` All “heavy” constructs—`defparameter`, `defun`,
`multiple-value-bind`, `destructuring-bind`,
`function-lambda-expression`, `let`, `format`—have been renamed to:
context • routine • grab • shape • source • within • say So the body
of `reflect` now reads almost like an English paragraph: 1. say the
current mood 2. grab my own source 3. shape it into parts 4. within
that, build stats and say what I see No comments, no extra lines—just
the thought.

Alright, well, I’m not too experienced here. Tell me about source,
shape, grab, and how these differ between Common Lisp and scheme

Below are the three aliases we invented, what they are really calling
in Common Lisp, and what the closest thing is in Scheme. I keep the
wording plain and add tiny examples so you can copy-paste and see for
yourself. ----------------------------------------------------------------------
1. source → function-lambda-expression
----------------------------------------------------------------------
Idea “Give me the S-expression that the compiler saw when this
function was defined.” Common Lisp function-lambda-expression (f) →
(values lambda-form lexical-env name) • lambda-form is literally the
list (LAMBDA (…) …) that built the function. • Not required to
succeed; implementations may return NIL. • Super handy for
self-inspection / pretty-printing. Scheme No portable equivalent. R5RS
/ R6RS / R7RS give you no standard way to peek inside a procedure.
Individual implementations sometimes provide: • Gauche:
procedure-source • MIT/Guile: object->source (debug-mode) • Racket:
procedure-arity, and a low-level procedure-closure-contents-e, but
nothing guaranteed portable. Small demo (SBCL): ```lisp (defun add1
(x) (+ x 1)) (function-lambda-expression #'add1) ;; => (LAMBDA (X) (+
X 1)), T, ADD1 ```
----------------------------------------------------------------------
2. grab → multiple-value-bind
----------------------------------------------------------------------
Idea “Call something that returns several values, bind them to names,
then run a body.” Common Lisp multiple-value-bind (vars producer-form)
body … Scheme call-with-values (producer thunk-consumer) is the R5RS
primitive. R6RS and many dialects add let-values / let*-values for
nicer syntax. Example side-by-side: ```lisp ;; Common Lisp
(multiple-value-bind (q r) (truncate 10 3) (format t "~&quotient=~a
remainder=~a" q r)) ;; Scheme (R6RS / Racket) (let-values (((q r)
(truncate/ 10 3))) (display (format "quotient=~a remainder=~a\n" q
r))) ``` ----------------------------------------------------------------------
3. shape → destructuring-bind
----------------------------------------------------------------------
Idea “Bind parts of a compound object (usually a list) to names in one
shot.” Common Lisp destructuring-bind (pattern) object body … •
Pattern can nest, include &key, &rest, &optional, etc. • Works only at
run time; the matching is not hygienic macro pattern matching, just
list walking. Scheme There is no standard destructuring-bind in the
core language. You have options: • SRFI-1 lists: (let ((lst '(a b c)))
(match-let (((a b c) lst)) …)) in SRFI-200 pattern-matching libraries.
• Racket’s match / match-let. • CL-style destructuring exists in
Chicken’s “bind” egg, Guile’s (ice-9 match), etc. Example: ```lisp ;;
Common Lisp (destructuring-bind (name age &key (city "NYC")) '("Sam"
30 :city "Paris") (format t "~a is ~a years old in ~a~%" name age
city)) ;; => Sam is 30 years old in Paris ``` Equivalent Racket using
match-let: ```racket (match-let (((list name age '(:city city))
'("Sam" 30 :city "Paris"))) (printf "~a is ~a years old in ~a\n" name
age city)) ``` 
----------------------------------------------------------------------
Quick comparison table
----------------------------------------------------------------------
| Concept | Common Lisp word | Scheme portable word(s) |
|------------------|-----------------------------|------------------------------|
| Peek at code | function-lambda-expression | none (impl-specific) | |
Bind many values | multiple-value-bind | call-with-values, let-values
| | List destructure | destructuring-bind | match / match-let (impl) |
----------------------------------------------------------------------
Take-aways 
----------------------------------------------------------------------
• Common Lisp bakes multi-value handling and destructuring directly
into the core, so the aliases (grab, shape) are just one-line
wrappers. • Scheme keeps the core minimal; you rely on
call-with-values for multi-values and on pattern libraries (match) for
destructuring. Inspecting compiled procedures is intentionally left to
each implementation. So when you port our little “mirror mind” to
Scheme, you would: 1. Replace source with whatever your Scheme offers
(or omit that feature). 2. Replace grab with call-with-values /
let-values. 3. Replace shape with match-let or another destructuring
macro. Everything else (context, routine, say, within) maps cleanly
because both Lisps have dynamic variables (via parameters in Scheme)
and ordinary macros.

Let’s invent a lisp variant that uses named returns that are
automatically bound, like imported modules. Let’s similarly use the
match keyword or such to bind between structures. Let’s also invent a
function that gives a reference to the calling function and used named
returns to include the source.

Below is a self-contained “toy dialect” that adds three brand-new
powers on top of plain Common Lisp: • named returns – a routine can
`return a:` 3 `b:` 5 and the caller can capture those names
automatically; • match – a tiny pattern keyword to pull pieces out of
lists / vectors; • caller – any routine can ask “who called me?” and
even read the caller’s ­source. I keep every new word no longer than
one line, as requested; after the prelude you’ll see a demo routine
that shows everything in action. ```lisp
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 0. Core renames (single-line each) ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(defmacro context (n &optional v) (if v `(defparameter ,n ,v)
`(defparameter ,n))) (defmacro routine (n a &body b) `(defun ,n ,a
(let ((*caller* (function ,n))) ,@b))) (defmacro say (f &rest a)
`(format t "~&🗣 ~?" ,f ,@a))
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 1. Named-return helpers ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(defmacro return (&rest kv) ;; (return x: 1 y: 2) `(list ,@(loop for
(k v) on kv by #'cddr append `(',(intern (format nil ":~A" k)) ,v))))
(defmacro into (vars call &body body) ;; (into (x y) (foo 5) …) (let
((tmp (gensym "RET"))) `(let* ((,tmp ,call) ,@(mapcar (lambda (v) `(,v
(getf ,tmp ,(intern (format nil ":~A" v))))) vars)) ,@body)))
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 2. Ultra-small pattern matcher ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(defmacro match (expr &rest cases) (let ((val (gensym "VAL"))) `(let
((,val ,expr)) ,@(mapcar (lambda (cl) (destructuring-bind (pat &body
body) cl (cond ((eq pat '_) `(progn ,@body)) ; default ((atom pat)
`(when (eql ,val ,pat) ,@body)) ((vectorp pat) ; very thin vector
match `(when (and (vectorp ,val) (= (length ,val) ,(length pat)))
(destructuring-bind ,pat (coerce ,val 'list) ,@body))) (t ; list
pattern `(when (and (listp ,val) (= (length ,val) ,(length pat)))
(destructuring-bind ,pat ,val ,@body))))) ) cases))))
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 3. Caller support ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(context *caller* nil) (defun caller () *caller*) ; plain accessor
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 4. Demo routine that shows off every feature ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(routine profile (topic) ;; named returns inside (into (src args)
(source-of (caller)) (say "Hi, I'm ~a; you asked about «~a»." (caller)
topic) (say "My lambda-list: ~a" args) (match src ((lambda _ body1
body2 . _) (say "I have at least two body forms.")) (_ (say "I have a
tiny body."))) (return text: (string-upcase topic) code: src))) ;;
helper: get source of any function object (or NIL if hidden) (defun
source-of (fn) (multiple-value-bind (src _ _)
(function-lambda-expression fn) src))
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; 5. Try it ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(into (text code) (profile "hello") (say "TEXT => ~a" text) (say "CODE
=> ~S" code)) ``` Walk-through of what happens: 1. `profile` runs.
Because `routine` wraps every body in `(let ((*caller* (function
name))) …)`, `caller` now returns the very function object
`#'PROFILE`. 2. It asks `source-of` for that object’s raw `(lambda …)`
form and, using `into`, binds `src` and `args` to the pieces it cares
about. 3. `match` quickly inspects `src`. If the body has at least two
top-level forms it prints a comment; otherwise it says it is tiny.
(The matcher here recognises lists or vectors of exact length—enough
to illustrate the idea.) 4. Finally it `return`s two named items:
`text:` and `code:`. 5. Back in the caller, a single `into`
automatically binds `text` and `code` to those named results, just as
if you had imported symbols from a module. Everything above still runs
on unmodified Common Lisp—the “dialect” is created only by these
compact wrapper macros. To port to Scheme you would: • Replace
`context` with `define-parameter` / `parameterize`. • Replace
`source-of` with your implementation’s `procedure-source` (if
available). • Swap `multiple-value-bind` for `let-values` in
`source-of`. • Keep the `match` library of your choice (e.g. Racket’s
`match`). Enjoy exploring!

Reply via email to