"Smart" comparison of functions in Racket - function

I've got a bit exotic situation. I need to compare functions, but rather by their "origin" than by "instances". Here what I actually mean:
(define-values (a b c d) (values #f #f #f #f))
(define (f x)
(let ([g (λ (y) (printf "Please tell ~a this is ~a\n" x y))]
[h (curry printf "Don't tell ~a this is ~a\n" x)])
(if a
(set! b g)
(set! a g))
(if c
(set! d h)
(set! c h))))
(f "me")
(f " me")
(a "possible")
(d "impossible")
(equal? a b) ; <==== Is it possible to compare these guys
(equal? c d) ; <==== to get #t in both cases?
In both cases we get two different "instances" of functions (even with different values captured), but both declared in the same location of the source code. Of course, getting the actual text of the body of those functions will solve the problem, but other answers here on SO tell that this is impossible in Racket. Are there some tricks that can help me?
Edit:
This is not the question on theoretical equivalence of functions. This is completely technical question, much rather on Racket's functions representation in a compiled code. So it can be reformulated, for example, in a following way: can I get the line number of some routine from 'user' code? I suppose this should be feasible because Racket debugger somehow obtains it.

It can be done even without support from racket internals if you control the code that makes the functions. If you keep a counter (or some identifier) that will denote the particular lambda it can wrap different closures in a struct that can have the same identity from macro expansion. Here is a demonstration:
#lang racket
;; makes a procedure object that can have other data connected to it
(struct proc (id obj)
#:property prop:procedure
(struct-field-index obj)
#:methods gen:custom-write
[(define (write-proc x port mode)
(display (format "#<procedure-id-~a>" (proc-id x)) port))])
;; compares the ids of two proc objects if they are proc objects
(define (proc-equal? a b)
(and (proc? a)
(proc? b)
(= (proc-id a) (proc-id b))))
;; extends equal?, candidate to provide
(define (equal*? a b)
(or (proc-equal? a b)
(equal? a b)))
;; the state we keep
(begin-for-syntax
(define unique-proc-id-per-code 0))
;; a macro that changes (lambda* ...) to
;; (proc expansion-id (lambda ...))
(define-syntax (lambda* stx)
(let ((proc-id unique-proc-id-per-code))
(set! unique-proc-id-per-code (add1 unique-proc-id-per-code))
#`(proc #,(datum->syntax stx proc-id) (lambda #,#(datum->syntax stx (cdr (syntax-e stx)))))))
;; test with making a counter
(define counter-from
(lambda* (from)
(lambda* ()
(begin0
from
(set! from (add1 from))))))
;; evaluatin the outer shows it has id 0
counter-from ; ==> #<procedure-id-0>
;; make two counters that both use the inner lambda
(define from10 (counter-from 10))
(define from20 (counter-from 20))
;; both have the same expansion id
from10 ; ==> #<procedure-id-1>
from20 ; ==> #<procedure-id-1>
;; they are not equal?
(equal? from10 from20) ; ==> #f (different object instances of proc)
;; but they are procedure-equal?
(proc-equal? from10 from20) ; ==> #t (same id, thus came from same macroexpansion)
Disclaimer: I'm more a schemer than a racketeer so this could perhaps have been done more elegantly and I have no idea what performance penalties this will give.

Related

Scheme - function to count occurrences of atom in argument

I'm new to scheme and trying to learn functions. I want to create a function where I can count all occurrences of the atom "a" in an argument. This is what I have written so far. I'm not sure what to write in the third condition. Please help out.
(define (count-a arg)
(COND
((null? arg) 0)
((eq? arg 'a) 1)
((list? arg) ( ___ + ( ___ count-a arg)))
(else 0)
))
This is the output i want:
(count-a 'a)
1
(count-a 'aa)
0
(count-a '(a))
1
(count-a '(ab c)
0
(count-a '(a (b c) (c (d a) a) (((a b)))))
5
(___ + ( ___ count-a arg)) doesn't seem right to me. Remember Scheme is a prefix language. It's (+ 1 2 3) instead of 1 + 2 + 3.
In the third one you have two lists parts. eg. '(a a) so you need to call count-a on the car and on the cdr of the list and add the results together. eg. (count-a '(a a)) should give the same result as (+ (count-a 'a) (count-a '(a))
Good luck
Welcome to Stack Overflow!
Solution:
(define (count-a arg)
(cond ((null? arg) 0)
((not (pair? arg))
(if (equal? arg 'a)
1
0))
;; At this point we know arg is a pair, and we recurse.
(else (+ (count-a (car arg)) (count-a (cdr arg))))))
Test:
Here are the tests you specified, compressed into a single line.
;; Chibi-Scheme REPL - other implementations might look different.
> (map count-a '(a aa (a) (ab c) (a (b c) (c (d a) a) (((a b))))))
(1 0 1 0 4)
You didn't say what you want to happen if arg is a dotted pair. But let's check it out just for fun.
> (map count-a '((ab . '()) (ab . a) (a . a)))
(0 1 2)
So when I run your last test on my code, it yields 4 where you expected 5. I maintain that my code is correct and your test specification is incorrect, as there are only four instances of 'a in the argument of count-a.
Discussion:
You specified in your headline that the thing the count-a function will be counting is an atom. So you have to check whether arg is an atom or not. Since Scheme doesn't have an atom? function, I'll assume that an atom is anything that's not '() and not a pair. (This is consistent with the atom function of Common Lisp, as well as other Lisp dialects.)
Since your code already deals with arg being '(), we only have to deal with arg being, or not being a pair.
If arg is not a pair and (equal? arg 'a), then (count-a arg) equals 1. Else, it equals 0.
If arg is a pair, we can recurse into car arg) and (cdr arg), however deeply nested arg may be, and increase our count whenever we find an atom that equals a.
Hope that helps.

LISP - Program to search a specific function through its parameters

For a course project I got to write a program in lisp.
The program should contain the most important lisp functions, their input and output parameters and maybe optional parameters.
For example: function - first, input - list, output - object (first member of list).
The program should work in 2 different ways:
You give the program the name of a function and it should return the function parameters.
You enter function parameters and if a function with these parameters exists, it should return the name of the function.
My questions:
What would be the right way to approach a task like this in lisp? I think maybe a tree would be a way to handle it? (make a tree with all functions and parameters and then write a program which handles it).
Does anyone have a better idea than that to approach this task? Or some suggestions where / how to start? Or Tutorials containing any info?
At the moment I'm a little lost how to start. Any help you can give would be highly appreciated.
English isn't my first language, so I hope everything is understandable.
Greetings.
First of all take a look to prepare your common lisp development environment. After that I think that you should, investigate:
create functions with defun,
declare types.
and things like that. Ffter that take a look to two common lisp functions:
documentation
describe
Here is a little example:
CL-USER> (defun my-sum (a b) "Add my-sum parameters A and B." (+ a b))
MY-SUM
CL-USER> (my-sum 2 3)
5 (3 bits, #x5, #o5, #b101)
CL-USER> (describe #'my-sum)
#<FUNCTION MY-SUM>
[compiled function]
Lambda-list: (A B)
Derived type: (FUNCTION (T T) (VALUES NUMBER &OPTIONAL))
Documentation:
Add my-sum parameters A and B.
Source form:
(SB-INT:NAMED-LAMBDA MY-SUM
(A B)
"Add my-sum parameters A and B."
(BLOCK MY-SUM (+ A B)))
; No values
CL-USER> (documentation 'my-sum 'function)
"Add my-sum parameters A and B."
CL-USER> (defun my-sum (a b) "Add my-sum parameters A and B." (declare (type fixnum a b)) (+ a b))
WARNING: redefining COMMON-LISP-USER::MY-SUM in DEFUN
MY-SUM
CL-USER> (describe #'my-sum)
#<FUNCTION MY-SUM>
[compiled function]
Lambda-list: (A B)
Derived type: (FUNCTION (FIXNUM FIXNUM)
(VALUES
(INTEGER -9223372036854775808 9223372036854775806)
&OPTIONAL))
Documentation:
Add my-sum parameters A and B.
Source form:
(SB-INT:NAMED-LAMBDA MY-SUM
(A B)
"Add my-sum parameters A and B."
(DECLARE (TYPE FIXNUM A B))
(BLOCK MY-SUM (+ A B)))
; No values
Finally, one last tip to work with strings from the output of describe:
CL-USER> (with-output-to-string (*standard-output*)
(describe #'my-sum))
"#<FUNCTION MY-SUM>
[compiled function]
Lambda-list: (A B)
Derived type: (FUNCTION (FIXNUM FIXNUM)
(VALUES
(INTEGER -9223372036854775808 9223372036854775806)
&OPTIONAL))
Documentation:
Add my-sum parameters A and B.
Source form:
(SB-INT:NAMED-LAMBDA MY-SUM
(A B)
\"Add my-sum parameters A and B.\"
(DECLARE (TYPE FIXNUM A B))
(BLOCK MY-SUM (+ A B)))
"
At face value, the task seems to be the construction of a simple symbolic database in memory, which is searchable in two ways. Entries in the database are understood to be functions. The "output parameters" can probably be understood as one or more return values. These things are not named in ANSI Lisp. A useful interpretation of the task is to give return values symbolic labels anyway. Moreover, we can perhaps use type symbols for the return values as well as parameters. So for instance, a database entry for the cons function might look like:
(cons (t t) cons) ;; function named cons takes two objects, returns a cons
The type t is the supertype of all types in ANSI Lisp; it means "any value".
A list of such records can be put into some global variable. Then we write a function that is perhaps named get-params-by-name such that:
(get-params-by-name 'cons) -> (t t)
and another one: get-names-by-params:
(get-names-by-params '(t t)) -> (cons)
This function returns all the matching functions, as a list. More than one function could have this signature.
The trick is then finding a good representation of optional and rest parameters. It could just be the same notation that the language uses:
(list (&rest t) list) ;; list takes rest arguments of any type, returns list
Since we are only interested in exact matches, we don't have to actually parse the &rest notation. When the user queries by parameter, their query object will be literally (&rest t), in that same syntax.
The equal function can be used to tell whether two lists of symbols are identical:
(equal '(&rest t) '(&rest t)) -> t
(equal '(t t) '(t t)) -> nil
So the exercise is not difficult: just mapping through lists, looking for matches.
(defun get-name-by-params (database params)
(let ((matching-entries (remove-if-not (lambda (entry)
(equal (second entry) params))
database)))
(mapcar #'first matching-entries))) ;; just the names, please
Here, the function takes the database list as a parameter, instead of referring to a global variable. The overall program into which we integrate this can provide alternative interfaces, but this is our low-level lookup function.
Test:
[1]> (get-name-by-params '((cons (t t) cons) (list (&rest t) list)) '(integer string))
NIL
[3]> (get-name-by-params '((cons (t t) cons) (list (&rest t) list)) '(t t))
(CONS)
[4]> (get-name-by-params '((cons (t t) cons) (list (&rest t) list)) '(&rest t))
(LIST)
I'd get clarification from the instructor whether this is the right interpretation of the vague requirements, before the assignment is due.
Given that this is a course project I'm going to provide an incomplete answer, and leave you to fill in the blanks.
What the program should do
My interpretation of what you're being asked to do is to provide a utility which will
given the name of a function return its argument list (called a 'lambda list' below);
given a lambda list return all the functions with that lambda list.
So, first of all you need to decide whether two lambda lists are the same or not. As an example is (x) the same as (y), as a lambda list? Yes, it is: the names of formal parameters only matter in the implementation of a function and you generally won't know them: both of these lambda lists mean 'function of one argument'.
The interestring thing is optional arguments of various kinds: (a &optional b) is clearly not the same as (a), but is the same as (b &optional c) but is it the same as (a &optional (b 1 bp))? In this code I say that yes, it is the same: default values and present parameters for optional arguments don't alter whether lambda lists are the same. That's because very often these are implementation details of functions.
A package
We'll put it into a package so it's clear what the interface is:
(defpackage :com.stackoverflow.lisp.fdesc-search
(:use :cl)
(:export
#:defun/recorded
#:record-function-description
#:clear-recorded-functions
#:name->lambda-list
#:lambda-list->names))
(in-package :com.stackoverflow.lisp.fdesc-search)
Recording information
So, to start with we need a mechanism of recording information about functions. We'll do this with a macro which is like defun but records information, which I'll call defun/recorded. We want to be able to record information about things even before the program exists & we do this by having defun/recorded stash 'pending' records on a list which, once the program exists, it will pull off and record properly. That lets us use defun/recorded throughout this code.
;;; These define whether there is a recorder, and if not where pending
;;; records should be stashed
;;;
(defvar *function-description-recorder* nil)
(defvar *pending-function-records* '())
(defmacro defun/recorded (name lambda-list &body forms)
"Like DEFUN but record function information."
;; This deals with bootstrapping by, if there is not yet a recording
;; function, stashing pending records in *PENDING-FUNCTION-RECORDS*,
;; which gets replayed into the recorder at the point it becomes
;; available.
`(progn
;; do the DEFUN first, which ensures that the LAMBDA-LIST is OK
(defun ,name ,lambda-list ,#forms)
(if *function-description-recorder*
(progn
(dolist (p (reverse *pending-function-records*))
(funcall *function-description-recorder*
(car p) (cdr p)))
(setf *pending-function-records* '())
(funcall *function-description-recorder*
',name ',lambda-list))
(push (cons ',name ',lambda-list)
*pending-function-records*))
',name))
Matching lambda lists, first steps
Now we want to be able to match lambda lists. Since we're obviously going to store things indexed by lambda list in some kind of tree we only really need to be able to deal with matching elements of them. And (see above) we don't care about things like default values. I've chosen to do this by first of all simplifying lambda lists to remove them and then matching the simplifies elements: there are other approaches.
simplify-lambda-list does the simplification and argument-matches-p tells you if two arguments match: the interesting bit is that it needs to know about lambda list keywords, which must match exactly, while everything else matches anything. The lambda-list-keywords constant is conveniently provided by the CL standard.
(defun/recorded simplify-lambda-list (ll)
;; Simplify a lambda list by replacing optional arguments with inits
;; by their names. This does not validate the list
(loop for a in ll
collect (etypecase a
(symbol a)
(list (first a)))))
(defun/recorded argument-matches-p (argument prototype)
;; Does an argument match a prototype.
(unless (symbolp argument)
(error "argument ~S isn't a symbol" argument))
(unless (symbolp prototype)
(error "prototype ~S isn't a symbol" prototype))
(if (find-if (lambda (k)
(or (eq argument k) (eq prototype k)))
lambda-list-keywords)
(eq argument prototype)
t))
Function descriptions (partial)
Information about functions is stored in objects called fdescs: the definition of these objects is not given here, but one question we need to answer is 'do two fdescs refer to versions of the same function?' Well, they do if the names of the functions are the same. Remember that function names do not have to be symbols ((defun (setf x) (...) ...) is allowed), so we must compare with equal not eql:
(defun/recorded fdescs-equivalent-p (fd1 fd2)
;; do FD1 & FD2 refer to the same function?
(equal (fdesc-name fd1)
(fdesc-name fd2)))
Storing fdescs indexed by lambda list (partial)
To index things efficiently by lambda list we build a tree. The nodes in this tree are called lambda-list-tree-nodes and their definition is not given here.
There are functions which intern a fdesc in a tree, and which return a list of fdescs indexed by a given lambda list. Neither have an implementation here, but this is what they look like:
(defun/recorded intern-lambda-list (lambda-list tree-node fdesc)
;; return the node where it was interned
...)
(defun/recorded lambda-list-fdescs (lambda-list tree-node)
;; Return a list of fdescs for a lambda list & T if there were any
;; or NIL & NIL if there were not (I don't think () & T is possible,
;; but it might be in some future version)
...)
The implementation of these functions will probably need to use use argument-matches-p and fdescs-equivalent-p.
The top-level databases (slightly partial)
Now we can define the top-level database objects: the root of the tree for indexing by lambda list, and a hashtable for indexing by name
(defvar *lambda-list-tree* (make-lambda-list-tree-node))
(defvar *tree-nodes-by-name* (make-hash-table :test #'equal))
Note that *tree-nodes-by-name* maps from names to the node where the information about that function is stored: that's done to make redefinition easier, as seen in the following function:
(defun/recorded record-function-description (name lambda-list)
"Record information about a function called NAME with lambda list LAMBDA-LIST.
Replace any existing information abot NAME. Return NAME."
(let ((fdesc (make-fdesc :name name :lambda-list lambda-list)))
;; First of all remove any existing information
(multiple-value-bind (node foundp) (gethash name *tree-nodes-by-name*)
(when foundp
(setf (lambda-list-tree-node-values node)
(delete fdesc (lambda-list-tree-node-values node)
:test #'fdescs-equivalent-p))))
(setf (gethash name *tree-nodes-by-name*)
(intern-lambda-list lambda-list *lambda-list-tree* fdesc)))
name)
Note that this function first of all looks up any existing information for name, and if it exists it removes it from the node where it was found. This makes sure that function redefinition does not leave obsolete information in the tree.
This function is the actual recorder which defun/recorded wants to know about, so tell it that:
(setf *function-description-recorder*
#'record-function-description)
Now the next time we invoke defun/recorded it will bootstrap the system by inserting all the the pending definitions.
record-function-description is part of the API to the package: it can be used to record information about functions we don't define.
User-interface functions
Apart from defun/recorded & record-function-description we want some functions which let us make enquiries into the database, as well as one which resets things:
(defun/recorded clear-recorded-functions ()
"Clear function description records. Return no values"
(setf *lambda-list-tree* (make-lambda-list-tree-node)
*tree-nodes-by-name* (make-hash-table :test #'equal))
(values))
(defun/recorded name->lambda-list (name)
"Look up a function by name.
Return either its lambda list & T if it is found, or NIL & NIL if not."
(multiple-value-bind (node foundp) (gethash name *tree-nodes-by-name*)
(if foundp
(values
(fdesc-lambda-list
(find-if (lambda (fd)
(equal (fdesc-name fd) name))
(lambda-list-tree-node-values node)))
t)
(values nil nil))))
(defun/recorded lambda-list->names (lambda-list)
"find function names matching a lambda-list.
Return a list of name & T if there are any, or NIL & NIL if none.
Note that lambda lists are matched so that argument names do not match, and arguments with default values or presentp parameters match just on the argument."
(multiple-value-bind (fdescs foundp) (lambda-list-fdescs lambda-list
*lambda-list-tree*)
(if foundp
(values (mapcar #'fdesc-name fdescs) t)
(values nil nil))))
And that's it.
Examples
After compiling, loading & using the package (with the missing bits added) we can first inject some useful extra functions into it (this is just a random scattering)
> (dolist (x '(car cdr null))
(record-function-description x '(thing)))
nil
> (dolist (x '(car cdr))
(record-function-description `(setf ,x) '(new thing)))
nil
> (record-function-description 'cons '(car cdr))
cons
> (record-function-description 'list '(&rest args))
Now we can make some enquiries:
> (lambda-list->names '(x))
(null cdr
car
lambda-list->names
name->lambda-list
com.stackoverflow.lisp.fdesc-search::simplify-lambda-list)
t
> (lambda-list->names '(&rest anything))
(list)
t
> (name->lambda-list 'cons)
(car cdr)
t
An example of storing things in trees
Below is some code which demonstrates one approach to storing information in trees (often known as tries). This is not usable above for a lot of reasons, but reading it might help implement the missing parts.
;;;; Storing things in trees of nodes
;;;
;;; Node protocol
;;;
;;; Nodes have values which may or may not be bound, and which may be
;;; assigned. Things may be interned in (trees of) nodes with a
;;; value, and the value associated with a thing may be retrieved
;;; along with an indicator as to whether it is present in the tree
;;; under the root.
;;;
(defgeneric node-value (node)
;; the immediate value of a node
)
(defgeneric (setf node-value) (new node)
;; Set the immediate value of a node
)
(defgeneric node-value-boundp (node)
;; Is a node's value bound?
)
(defgeneric intern-thing (root thing value)
;; intern a thing in a root, returning the value
(:method :around (root thing value)
;; Lazy: this arround method just makes sure that primary methods
;; don't need to beother returning the value
(call-next-method)
value))
(defgeneric thing-value (root thing)
;; return two values: the value of THING in ROOT and T if is it present, or
;; NIL & NIL if not
)
;;; Implementatation for STRING-TRIE-NODEs, which store strings
;;;
;;; The performance of these will be bad if large numbers of strings
;;; with characters from a large alphabet are stored: how might you
;;; fix this without making the nodes enormous?
;;;
(defclass string-trie-node ()
;; a node in a string trie. This is conceptually some kind of
;; special case of an abstract 'node' class, but that doesn't
;; actually exist.
((children-map :accessor string-trie-node-children-map
:initform '())
(value :accessor node-value)))
(defmethod node-value-boundp ((node string-trie-node))
(slot-boundp node 'value))
(defmethod intern-thing ((root string-trie-node) (thing string) value)
;; intern a string into a STRING-TRIE-NODE, storing VALUE
(let ((pmax (length thing)))
(labels ((intern-loop (node p)
(if (= p pmax)
(setf (node-value node) value)
(let ((next-maybe (assoc (char thing p)
(string-trie-node-children-map node)
:test #'char=)))
(if next-maybe
(intern-loop (cdr next-maybe) (1+ p))
(let ((next (cons (char thing p)
(make-instance (class-of node)))))
(push next (string-trie-node-children-map node))
(intern-loop (cdr next) (1+ p))))))))
(intern-loop root 0))))
(defmethod thing-value ((root string-trie-node) (thing string))
;; Return the value associated with a string in a node & T or NIL &
;; NIL if there is no value for this string
(let ((pmax (length thing)))
(labels ((value-loop (node p)
(if (= p pmax)
(if (node-value-boundp node)
(values (node-value node) t)
(values nil nil))
(let ((next (assoc (char thing p)
(string-trie-node-children-map node)
:test #'char=)))
(if next
(value-loop (cdr next) (1+ p))
(values nil nil))))))
(value-loop root 0))))
;;; Draw node trees in LW
;;;
#+LispWorks
(defgeneric graph-node-tree (node))
(:method ((node string-trie-node))
(capi:contain
(make-instance 'capi:graph-pane
:roots `((nil . ,node))
:children-function (lambda (e)
(string-trie-node-children-map (cdr e)))
:edge-pane-function (lambda (pane parent child)
(declare (ignore pane parent))
(make-instance
'capi:labelled-line-pinboard-object
:text (format nil "~A" (car child))))
:print-function (lambda (n)
(let ((node (cdr n)))
(format nil "~A"
(if (node-value-boundp node)
(node-value node)
""))))))))

How to recreate apply in scheme

how would i create the function apply in scheme?
A my-apply function that does the same thing as it.
(define (my-apply fn lst)
(if (null? lst)
I'm not sure where to go from here or how to start.
I think apply is "more fundamental" than eval, so the following is cheating:
(define (my-apply func args)
(eval `(,func ,#args)))
I don't think you can do it without eval.
I created a lisp interpreter a while back and it has eval and macros, but it didn't have apply. I wondered if there was a way I could make my interpreter support apply so made an effort to try this. Here is my first attempt:
(define (my-apply proc args)
(eval (cons proc args)))
This clearly doesn't work since the function and the list of arguments gets evaluated twice. eg. (my-apply cons '(a b)) will give you (cons a b) and not (cons 'a 'b). I then thought that this might be a job for a macro but threw the idea away since the list of arguments are not known at macro expansion time. Procedure it needs to be so I though I could quote the list before I pass it to eval.
(define (my-apply proc args)
(define (q v)
(list 'quote v))
(eval (cons proc (map q args))))
This actually works, but this does a lot more work than a native apply would do to undo the job eval does.
If you are not allowed to use eval you are truely out of luck. It cannot be done. The same goes for implementing eval without using apply since then you have no way of doing primitives.
(define (my-two-arg-apply f a)
(let ((l (length a)))
(cond ((= l 0) (f))
((= l 1) (f (car a)))
((= l 2) (f (car a) (cadr a))
...
((= l 5) (f (car a) (cadr a) ... (caddddr a)))
...
((= l 7) (f (car a) (cadr a) ... (caddddr a)
(list-ref a 5) (list-ref a 6)))
... ;; lots more cases
(else (error "argument passing limit exceeded")))))
A macro could be used to generate the large quantity of code needed.
error was introduced in R6RS. Amazingly, Scheme programs had no reasonable way to report errors before that.
Don't even think about making a pop macro and using the pattern (f (pop a) (pop a) ... (pop a)); Scheme doesn't have a defined evaluation order for function arguments unlike some other Lisp dialects like ANSI CL.

LISP dynamically define functions

I want to define a function with a parameter that defines another function with that parameter as the name.
example that dont work:
(DEFUN custom (name op const var)
(DEFUN name (var) (op const var)))
The problem is that name isnt evaluated and so the function that is defined is always called name.
I know that FUNCALL and APPLY can evaluate parameter dynamically, but i don't know how to call FUNCALL DEFUN... correctly.
I don't think you can use nested defuns.
You can either use a defun to return a lambda:
(defun custom (op const)
(lambda (arg) (funcall op const arg)))
and then use fdefinition:
(setf (fdefinition '+42) (custom '+ '42))
or use defmacro:
(defmacro custom (name op const)
(let ((arg (gensym)))
`(defun ,name (,arg)
(,op ,const ,arg))))
(custom +42 + 42)
PS. I think you need to explain why you are trying to do this, then we will be able to explain your options better.
It seems to me you might want to curry a function. Imagine you did this:
(defun curry (op arg1)
(lambda (&rest args) (apply op (cons arg1 args))))
(funcall (curry #'+ 10) 20) ; ==> 30
(mapcar (curry #'+ 10) '(1 2 3 4)) ; ==> (11 12 13 14)
Now defun makes a function in the global namespace always. It's not like in Scheme where it creates a closure. To do the same as defun we use symbol-function and setf:
(defun create-curried (name op arg1)
(setf (symbol-function name)
(lambda (&rest args) (apply op (cons arg1 args)))))
(create-curried '+x #'+ 10) ; ==> function
(+x 20) ; ==> 30
;; since it's a function, it even works with higher order functions
(mapcar create-curried '(+x -x /x *x) (list #'+ #'- #'/ #'*) '(10 10 10 10))
(/x 2) ; ==> 5
Last. With macros you can prettify it.
(defmacro defun-curried (newname oldname arg)
(if (and (symbolp newname) (symbolp oldname))
`(create-curried ',newname (function ,oldname) ,arg)
(error "Newname and Oldname need to be symbols")))
(defun-curried +xx + 20)
(+xx 10) ; ==> 30
oldname is taken from the lexical scope so you may use flet or labels with this but it ends up being global, just like with defun.
The main problem is that DEFUN isn't a function, it's a macro that treats its arguments specially (specifically, it doesn't evaluate "the function name", "the argument list", not "the function body").
You could probably make something work by careful use of (setf (symbol-function ...) ...), something like:
(defun define-custom-function (name op const)
(setf (symbol-function name) (lambda (var) (funcall op const var))))
This binds the function definition of the symbol to an anonymous function that calls your "operator" on your fed-in constant.
* (defun define-custom-function (name op const)
(setf (symbol-function name) (lambda (var) (funcall op const var))))
DEFINE-CUSTOM-FUNCTION
* (define-custom-function 'add3 #'+ 3)
#<CLOSURE (LAMBDA (VAR) :IN DEFINE-CUSTOM-FUNCTION) {1002A4760B}>
* (add3 5)
8
However, unless you absolutely need to define (or re-define) these custom functions dynamically, you are probably better off defining a custom DEFUN-like macro.

Break loop and return in Racket Scheme

I'm trying to find the first missing key in a hash table, that should contain keys [1 ... N], using Scheme.
So far, I have the following code:
(define (find-missing n ht)
(define c 1)
(let forVertices ()
(cond (not (hash-has-key? ht c))
(c)
)
(set! c (+ c 1))
(when (>= n c) (forVertices))
)
)
When I execute the function to test it, nothing is returned. What am I doing wrong?
You have a couple of problems with the parentheses, and the else case is missing. This should fix the mistakes:
(define (find-missing n ht)
(define c 1)
(let forVertices ()
(cond ((not (hash-has-key? ht c))
c)
(else
(set! c (+ c 1))
(when (>= n c)
(forVertices))))))
… But you should be aware that the way you wrote the procedure is not idiomatic, at all. In general, in Scheme you should avoid mutating state (the set! operation), you can write an equivalent procedure by correctly setting up the recursion and passing the right parameters. Also, it's a good idea to return something whenever the recursion exits (for instance: #f), otherwise your procedure will return #<void> if there are no keys missing. Here, this is what I mean:
(define (find-missing n ht)
(let forVertices ((c 1))
(cond ((> c n) #f)
((not (hash-has-key? ht c)) c)
(else (forVertices (+ c 1))))))