Defining a macro to take an input stream - macros

I'm attempting to make a macro that will take an input stream and do something different depending on the contents of the first line read, and then read further input. I'm having trouble just having a macro that will take an input stream and read some values from it.
A contrived example:
(defmacro read-and-print (&optional in)
`(print
,(if (string= (read-line in) "greet")
`(concatenate 'string "hello" (read-line ,in))
`(read-line ,in))))
(with-input-from-string (in "greet
bob") (read-and-print in))
but even that is producing the following error
There is no applicable method for the generic function
#<STANDARD-GENERIC-FUNCTION SB-GRAY:STREAM-READ-LINE (1)>
when called with arguments
(IN).
[Condition of type SB-INT:COMPILED-PROGRAM-ERROR]
The thing that's really baffling me is even changing the function to take a string for the first line isn't working:
(defmacro read-and-print (command &optional in)
`(print
,(if (string= command "greet")
`(concatenate 'string "hello " (read-line ,in))
`(read-line ,in))))
(with-input-from-string (in "greet
bob")
(read-and-print (read-string in) in))
This gives me
The value
(READ-LINE IN)
is not of type
(OR (VECTOR CHARACTER) (VECTOR NIL) BASE-STRING SYMBOL CHARACTER)
when binding SB-IMPL::STRING1
[Condition of type SB-INT:COMPILED-PROGRAM-ERROR]
While this executes completely fine:
(with-input-from-string (in "greet
bob")
(read-and-print "greet" in))
Is there something special about the with-input-from-string macro that I'm missing? I suspect I'm missing something very obvious about macros, but googling has gotten me nowhere.

What you asked
Macros are a code generation tool.
They do not evaluate their arguments.
Your with-input-from-string example works because strings are self-evaluating. If you quite the string literal, you will get an error.
What you should have asked
You do not need a macro here. Use a function instead.
When deciding between a function and a macro, you need to ask yourself:
Am I defining a new syntax?
Does the code generate more code?
Unless you understand the questions and answer yes, you should be using functions.
See also How does Lisp let you redefine the language itself?

Your macro:
(defmacro read-and-print (&optional in)
`(print
,(if (string= (read-line in) "greet")
`(concatenate 'string "hello" (read-line ,in))
`(read-line ,in))))
But ,(if ... in ...) makes no sense, since the value of in typically isn't a stream at macro expansion time, but code (a symbol, an expression, ...). Since your code is not executing and the macro sees the source (and not the values of something which has not been executed yet) you can't do that. You can't also not usefully repair that: It's just the wrong approach. Use a function instead.
Use a function:
CL-USER 17 > (defun read-and-print (&optional in)
(if (string= (read-line in) "greet")
(concatenate 'string "hello" (read-line in))
(read-line in)))
READ-AND-PRINT
CL-USER 18 > (with-input-from-string (in "greet
foo
bar")
(read-and-print in))
"hellofoo"
Using a macro
You still can write it as a macro, but then you need to generate the code so that it runs at runtime, and not at macro-expansion time:
(defmacro read-and-print (&optional in)
`(print
(if (string= (read-line ,in) "greet")
(concatenate 'string "hello" (read-line ,in))
(read-line ,in))))
Note: one would actually might want to handle that in is not evaluated multiple times.
This macro would give you the advantage that the code is inlined.
This macro would give you the disadvantage that the code is inlined.
The function above gives you the advantage that the code typically is not inlined.
The function above gives you the advantage that the code can optionally be inlined, by telling the compiler to do so with an inline declaration.

Related

How can I modify the #+ and #- readtable macros in Lisp?

Short version:
I want to change the #+ and #- reader macros to apply to all immediately subsequent tokens starting with ##, in addition to the following token. Therefore, the following code...
#+somefeature
##someattribute1
##someattribute2
(defun ...)
...would, in the absence of somefeature, result in no code.
Long version:
I have written my own readtable-macros which apply transformations to subsequent code. For example:
##traced
(defun ...)
This yields a function that writes its arguments and return values to a file, for debugging.
This fails, however, when used in conjunction with the #+ reader macro:
#+somefeature
##traced
(defun ...)
In the absence of somefeature, the function continues to be defined, albeit without the ##traced modification. This is obviously not the desired outcome.
One possible solution would be to use progn, as follows:
#+somefeature
(progn
##traced
(defun ...))
But that's kind of ugly.
I would like to modify the #+ and #- reader macros, such that they may consume more than one token. Something like this:
(defun conditional-syntax-reader (stream subchar arg)
; If the conditional fails, consume subsequent tokens while they
; start with ##, then consume the next token.
)
(setf *readtable* (copy-readtable))
(set-dispatch-macro-character #\# #\+ #'conditional-syntax-reader)
(set-dispatch-macro-character #\# #\- #'conditional-syntax-reader)
The problem is, I don't know how to "delegate" to the original reader macros; and I don't understand enough about how they were implemented to re-implement them myself in their entirety.
A naive approach would be:
(defun consume-tokens-recursively (stream)
(let ((token (read stream t nil t)))
(when (string= "##" (subseq (symbol-string token) 0 2))
(consume-tokens-recursively stream)))) ; recurse
(defun conditional-syntax-reader (stream subchar arg)
(unless (member (read stream t nil t) *features*)
(consume-tokens-recursively stream)))
However, I'm given to believe that this wouldn't be sufficient:
The #+ syntax operates by first reading the feature specification and then skipping over the form if the feature is false. This skipping of a form is a bit tricky because of the possibility of user-defined macro characters and side effects caused by the #. and #, constructions. It is accomplished by binding the variable read-suppress to a non-nil value and then calling the read function.
This seems to imply that I can just let ((*read-suppress* t)) when using read to solve the issue. Is that right?
EDIT 1
Upon further analysis, it seems the problem is caused by not knowing how many tokens to consume. Consider the following attributes:
##export expects one argument: the (defun ...) to export.
##traced expects two arguments: the debug level and the (defun ...) to trace.
Example:
#+somefeature
##export
##traced 3
(defun ...)
It turns out that #+ and #- are capable of suppressing all these tokens; but there is a huge problem!
When under a suppressing #+ or #-, (read) returns NIL!
Example:
(defun annotation-syntax-reader (stream subchar arg)
(case (read stream t nil t)
('export
(let ((defun-form (read stream t nil t)))))
; do something
('traced
(let* ((debug-level (read stream t nil t))
(defun-form (read stream t nil t)))))))
; do something
(setf *readtable* (copy-readtable))
(set-dispatch-macro-character #\# #\# #'annotation-syntax-reader)
#+(or) ##traced 3 (defun ...)
The ##traced token is being suppressed by the #+. In this situation, all the (read) calls in (annotation-syntax-reader) consume real tokens but return NIL!
Therefore, the traced token is consumed, but the case fails. No additional tokens are thus consumed; and control leaves the scope of the #+.
The (defun ...) clause is executed as normal, and the function comes into being. Clearly not the desired outcome.
The standard readtable
Changing the macros for #+ and #- is a bit excessive solution I think, but in any case remember to not actually change the standard readtable (as you did, but its important to repeat in the answer)
The consequences are undefined if an attempt is made to modify the standard readtable. To achieve the effect of altering or extending standard syntax, a copy of the standard readtable can be created; see the function copy-readtable.
§2.1.1.2 The Standard Readtable
Now, maybe I'm missing something (please give us a hint about how your reader macro is defined if so), but I think it is possible to avoid that and write your custom macros in a way that works for your use case.
Reader macro
Let's define a simple macro as follows:
CL-USER> (defun my-reader (stream char)
(declare (ignore char))
(let ((name (read stream)
(form (read stream))
(unless *read-suppress*
`(with-decoration ,name ,form)))
MY-READER
[NB: This was edited to take into account *read-suppress*: the code always read two forms, but returns nil in case it is being ignored. In the comments you say that you may need to read an indefinite number of forms based on the name of the decoration, but with *read-suppress* the recursive calls to read return nil for symbols, so you don't know which decoration is being applied. In that case it might be better to wrap some arguments in a literal list, or parse the stream manually (read-char, etc.). Also, since you are using a dispatching macro, maybe you can add a numerical argument if you want the decoration to be applied to more than one form (#2#inline), but that could be a bad idea when later the decorated code is being modified.]
Here the reader does a minimal job, namely build a form that is intended to be macroexpanded later. I don't even need to define with-decoration for now, as I'm interested in the read step. The intent is to read the next token (presumably a symbol that indicates what decoration is being applied, and a form to decorate).
I'm binding this macro to a unused character:
CL-USER> (set-macro-character #\§ 'my-reader)
T
Here when I test the macro it wraps the following form:
CL-USER> (read-from-string "§test (defun)")
(WITH-DECORATION TEST (DEFUN))
13 (4 bits, #xD, #o15, #b1101)
And here it works with a preceding QUOTE too, the apostrophe reader grabs the next form, which recursively reads two forms:
CL-USER> '§test (defun)
(WITH-DECORATION TEST (DEFUN))
Likewise, a conditional reader macro will ignore all the next lines:
CL-USER> #+(or) t
; No values
CL-USER> #+(or) §test (defun)
; No values
CL-USER> #+(or) §one §two §three (defun)
; No values
Decoration macro
If you use this syntax, you'll have nested decorated forms:
CL-USER> '§one §two (defun test ())
(WITH-DECORATION ONE (WITH-DECORATION TWO (DEFUN TEST ())))
With respect to defun in toplevel positions, you can arrange for your macros to unwrap the nesting (not completely tested, there might be bugs):
(defun unwrap-decorations (form stack)
(etypecase form
(cons (destructuring-bind (head . tail) form
(case head
(with-decoration (destructuring-bind (token form) tail
(unwrap-decorations form (cons token stack))))
(t `(with-decorations ,(reverse stack) ,form)))))))
CL-USER> (unwrap-decorations ** nil)
(WITH-DECORATIONS (ONE TWO) (DEFUN TEST ()))
And in turn, with-decorations might know about DEFUN forms and how to annotate them as necessary.
For the moment, our original macro is only the following (it needs more error checking):
(defmacro with-decoration (&whole whole &rest args)
(unwrap-decorations whole nil))
For the sake of our example, let's define a generic annotation mechanism:
CL-USER> (defgeneric expand-decoration (type name rest))
#<STANDARD-GENERIC-FUNCTION COMMON-LISP-USER::EXPAND-DECORATION (0)>
It is used in with-decorations to dispatch on an appropriate expander for each decoration. Keep in mind that all the efforts here are to keep defun in a top-level positions (under a progn), a recursive annotation would let evaluation happens (in the case of defun, it would result in the name of the function being defined), and the annotation could be done on the result.
The main macro is then here, with a kind of fold (reduce) mechanism where the forms are decorated using the resulting expansion so far. This allows for expanders to place code before or after the main form (or do other fancy things):
(defmacro with-decorations ((&rest decorations) form)
(etypecase form
(cons (destructuring-bind (head . tail) form
(ecase head
(defun (destructuring-bind (name args . body) tail
`(progn
,#(loop
for b = `((defun ,name ,args ,#body)) then forms
for d in decorations
for forms = (expand-decoration d name b)
finally (return forms))))))))))
(nb. here above we only care about defun but the loop should probably be done outside of the dispatching thing, along with a way to indicate to expander methods that a function is being expanded; well, it could be better)
Say, for example, you want to declare a function as inline, then the declaration must happen before (so that the compiler can know the source code must be kept):
(defmethod expand-decoration ((_ (eql 'inline)) name rest)
`((declaim (inline ,name)) ,#rest))
Likewise, if you want to export the name of the function being defined, you can export it after the function is defined (order is not really important here):
(defmethod expand-decoration ((_ (eql 'export)) name rest)
`(,#rest (export ',name)))
The resulting code allows you to have a single (progn ...) form with a defun in toplevel position:
CL-USER> (macroexpand '§inline §export (defun my-test-fn () "hello"))
(PROGN
(DECLAIM (INLINE MY-TEST-FN))
(DEFUN MY-TEST-FN () "hello")
(EXPORT 'MY-TEST-FN))

Can I put condition in emacs lisp macro?

How to achieve something like this?
(defmacro mood (x)
(if (equal (symbol-name x) "t")
`(defun happy ()
(message "Happy"))
`(defun sad ()
(message "Sad")))
)
My aim is to create different function base on argument.
Is there any problem doing so?
Edit 2: You're right -- for cases in which the code being evaluated at expansion-time is entirely dependent on the values of the (unevaluated) macro arguments, I believe it is safe for the macro's returned form to be generated conditionally, based upon those arguments.
You just need to be aware that any behaviour which is conditional upon dynamic values needs to be dealt with as a part of the expanded form.
(e.g. if the macro argument were a variable, and you were testing the value of the variable in your condition, it would be unsafe for that test to occur at expansion time, as that value is liable to vary between the macro's expansion time, and the time(s) that the expanded code is evaluated.)
So the specific example in your question is indeed safe as-is, and therefore my variations (below) are not actually necessary in this case. However expansion-time evaluations are certainly something you will want to be cautious about in general.
Initial answer follows...
Macros are expanded at compile time. (Or in recent versions of Emacs, should no byte-compiled version of the library be available, they will usually be compiled "eagerly" at load time).
In these scenarios, any code which is not a part of the form returned by the macro will be evaluated at most once per session, but quite likely just once ever for a given expansion of the code (whereas the expanded code might then be called numerous times).
If you need your expanded code to act conditionally at run-time, the conditions must be a part of the form returned by the macro.
Edit: For example, I imagine you actually wanted to write something more like:
(defmacro mood (x)
`(if (equal (symbol-name ,x) "t")
(defun happy ()
(message "Happy"))
(defun sad ()
(message "Sad"))))
Although you would (almost) never want to compare symbols by comparing their symbol-name. You've already made the assumption that the macro argument will evaluate to a symbol, so just compare the symbols directly with eq:
(defmacro mood (x)
`(if (eq ,x t)
(defun happy ()
(message "Happy"))
(defun sad ()
(message "Sad"))))
Then for example, (mood 'foo) expands to (courtesy of M-x pp-macroexpand-last-sexp):
(if
(eq 'foo t)
(defun happy nil
(message "Happy"))
(defun sad nil
(message "Sad")))
There is no problem defining it. You code, actually, almost works:
(defmacro mood (x)
(if (equal x t)
`(defun happy ()
(message "Happy"))
`(defun sad ()
(message "Sad"))))
Since if is outside of back-quotes, we can examine the value of x directly. Expanding this definition with different arguments shows that different functions are defined:
> (macroexpand '(mood t))
(defalias (quote happy) (function (lambda nil (message "Happy"))))
> (macroexpand '(mood nil))
(defalias (quote sad) (function (lambda nil (message "Sad"))))

Lisp evaluate variable in macro expression

I have the following function (I am a very beginner at Lisp):
(defun my-fun (a b)
(my-commandsend-and-reply-macro (cmd)
(:reply (ok result)
(do-something a b result)))
)
where my-commandsend-and-reply-macro is a macro written by another programmer. I am unable to modify it.
my-commandsend-and-reply-macro sends a command (in this example cmd) to a server process (it is written in another programming language) and then waits for its answer.
The answer is processed then in the macro using the user-given ":reply part of the code". The list (ok result) is a kind of pattern, in the macro a destructuring-bind destructures and binds the proper parts of the answer to ok and result (ok is just a flag). After this the other user-given lines of the ":reply part" are excuted. (for result processing)
I would like to do the following:
1, send a command like to the other process (this is ok)
2, call a function (like do-something) using the result AND using some other parameters which are the actual parameters of my-fun (this part fails...)
How can I do this? I think the problem is that a and b are not evaluated before the macro expansion and when the macro is expanded Lisp searches for a local a and b but there is no a or b. Is there any way to evaluate a and b? (so the macro could treat them like concrete values)
This is the macro def: (written by another programmer)
(defmacro* my-commandsend-and-reply-macro ((cmd &rest args) &body body)
`(progn
(with-request-id ()
(setf (gethash *request-id* *my-callbacks*)
(lambda (status &rest status-args)
(case status
,#(loop for (kind . clause) in body when (eql kind :reply)
collect
(destructuring-bind
((status-flag &rest lambda-form-pattern)
&body action-given-by-user) clause
`(,status-flag
(destructuring-bind ,lambda-form-pattern status-args
,#action-given-by-user))))
((error)
(message "Error: %s" (elt (elt status-args 0) 1))))))
(apply #'send-command-to-process *request-id* cmd args)))))
Def of with-request-id:
(defmacro* with-request-id ((&rest vars) &body body)
"Send `getid' to the server, and call `body' once the response
with the new ID has arrived. By then, global variable `*request-id*'
is bound to the latest request ID."
`(progn
(when (not (server-is-running))
(error "Server isn't running!"))
(when *reqid-queue*
(error "Some internal error occured. Please, restart the program!"))
(lexical-let (,#(loop for var in vars
collect `(,var ,var)))
(setf *reqid-queue* (lambda ()
(unwind-protect
(progn ,#body)
(setf *reqid-queue* nil)))))
(get-id)))
And getting id from the other process:
(defun get-id ()
(send-command-to-process 'getid))
Without looking into your code at all (apologies -- no time) ---
a and b are evaluated by the function my-fun. All functions evaluate their arguments to begin with -- only macros and special forms do not necessarily evaluate all of their arguments.
But those a and b values are not passed to the macro -- the only thing passed to it is the unevaluated sexp that is bound to cmd. And you do not even define cmd in your function!
What you need to do is substitute the values of a and b into the cmd sexp. You have not shown how cmd is defined/constructed, at all. Construct it using the values of a and b, and you should be OK.
To construct the cmd sexp, remember that you can use backquote syntax to simplify things, using comma syntax to pass the values of a and b. E.g.
(let ((cmd `(some funny (expression) that ((uses)) ,a AND ,b)))
code-that-uses-CMD)
This assumes that the code you pass to the macro does not need the variables a and b, and it needs only their values.
When the function my-fun is called the arguments have already been evaluated so it's not clear to me what is the problem you are facing.
The only strange thing I see is that the macro is un-hygienic and so if your arguments are named instead of a and b for example status or status-args you're going to be in trouble because the expression
(do-something <a> <b> results)
will be compiled in a context where those names have been reused by the macro.

ELISP Macro passing by symbol instead of list

(defmacro flycheck-define-clike-checker (name command modes)
`(flycheck-declare-checker ,(intern (format "flycheck-checker-%s" name))
,(format "A %s checker using %s" name (car command))
:command '(,#command source-inplace)
:error-patterns
'(("^\\(?1:.*\\):\\(?2:[0-9]+\\):\\(?3:[0-9]+\\): error: \\(?4:.*\\)$"
error)
("^\\(?1:.*\\):\\(?2:[0-9]+\\):\\(?3:[0-9]+\\): warning: \\(?4:.*\\)$"
warning))
:modes ',modes))
(flycheck-define-clike-checker c
("gcc" "-fsyntax-only" "-Wall" "-Wextra")
c-mode)
Above is the code that i took from https://github.com/jedrz/.emacs.d/blob/master/setup-flycheck.el
It doesn't do anything much apart from defining a checker for flycheck which can be found https://github.com/lunaryorn/flycheck
My problem is trivial and i have already spent a day on it and i am more confused.
The second part of the code uses the defined macro to call flycheck to register a compiler
(flycheck-define-clike-checker c
("gcc" "-fsyntax-only" "-Wall" "-Wextra")
c-mode)
Above code works perfectly.
But since i wanted my compiler to have some dynamic includes et all, I have a variable defined as
(defvar efx-flycheck-c-command '("gcc" "-fsyntax-only" "-Wall" "-Wextra"))
when i pass that to the macro like
(flycheck-define-clike-checker c
efx-flycheck-c-command
c-mode)
i receive a compilation error
Debugger entered--Lisp error: (wrong-type-argument sequencep efx-flycheck-c-command)
append(efx-flycheck-c-command (source-inplace))
(list (quote quote) (append command (quote (source-inplace))))
(list (quote flycheck-declare-checker) (intern (format "flycheck-checker-%s" name)) (format "A %s checker" name) (quote :command) (list (quote quote) (app$
(\` (flycheck-declare-checker (\, (intern (format "flycheck-checker-%s" name))) (\, (format "A %s checker" name)) :command (quote ((\,# command) source-in$
(lambda (name command modes) (\` (flycheck-declare-checker (\, (intern (format "flycheck-checker-%s" name))) (\, (format "A %s checker" name)) :command (q$
(flycheck-define-clike-checker c efx-flycheck-c-command c-mode)
eval((flycheck-define-clike-checker c efx-flycheck-c-command c-mode) nil)
eval-last-sexp-1(nil)
eval-last-sexp(nil)
call-interactively(eval-last-sexp nil nil)
I guess i confused in how the macro expands in elisp.
Please help!
As a general rule, you're better off using a defun than a defmacro, except when defun is really inconvenient/impossible to use. In your case, a defun indeed makes more sense. The only downside is that you need to quote the c and c-mode arguments.
You need to decide whether you want the command argument to be evaluated or unevaluated. An unevaluated argument allows you to type lists without quoting them, i.e. ("gcc" "-Wall") instead of '("gcc" "-Wall"), at the cost of not being able to pass a variable as the argument. An evaluated argument enables you to provide variables (or indeed arbitrary expressions) to the macro, at the cost of having to quote simple lists.
Normally, to evaluate the macro argument in backticks, you'd just use the , operator. However, you're already using the ,# operator, and you're mentioning command twice, so it's better to explicitly evaluate it using eval:
(defmacro flycheck-define-clike-checker (name command modes)
(let ((command (eval command)))
`(flycheck-declare-checker ,(intern (format "flycheck-checker-%s" name))
,(format "A %s checker using %s" name (car command))
:command '(,#command source-inplace)
:error-patterns
'(("^\\(?1:.*\\):\\(?2:[0-9]+\\):\\(?3:[0-9]+\\): error: \\(?4:.*\\)$"
error)
("^\\(?1:.*\\):\\(?2:[0-9]+\\):\\(?3:[0-9]+\\): warning: \\(?4:.*\\)$"
warning))
:modes ',modes)))
With the power of defmacro at your disposal, you can even go one step further and define that the macro is evaluates if it is a symbol, otherwise it's used as-is. This would allow you to have your cake and eat it, i.e. be able to pass both variable names and literal lists. The cost of this would be reduced consistency with normal evaluation rules—you would be able to pass a list or a variable, but not an arbitrary expression such as a function call, which would unpleasantly surprise the users of the macro. Because of that the implementation is left as an exercise for the reader.

Can you create interactive functions in an Emacs Lisp macro?

I'm trying to write a macro in emacs lisp to create some ‘helper functions.’
Ultimately, my helper functions will be more useful than what I have here. I realize that there may be better/more intuitive ways to accomplish the same thing (please post) but my basic question is why won't this work/what am I doing wrong:
(defmacro deftext (functionname texttoinsert)
`(defun ,(make-symbol (concatenate 'string "text-" functionname)) ()
(interactive)
(insert-string ,texttoinsert)))
(deftext "swallow" "What is the flight speed velocity of a laden swallow?")
(deftext "ni" "What is the flight speed velocity of a laden swallow?")
If I take the output of the macroexpand and evaluate that, I get the interactive functions I was intending to get with the macro, but even though the macro runs and appears to evaluate, I can't call M-x text-ni or text-swallow.
This does what you want:
(defmacro deftext (functionname texttoinsert)
(let ((funsymbol (intern (concat "text-" functionname))))
`(defun ,funsymbol () (interactive) (insert-string ,texttoinsert))))
As has been pointed out, the solution is to use intern instead of make-symbol.
It's possible to create multiple independent symbols with the same name, but only one of them can be the canonical symbol for the given name -- i.e. the symbol you will obtain when you refer to it elsewhere.
intern returns the canonical symbol for the given name. It creates a new symbol only if no interned symbol by that name already exists. This means that it will only ever create one symbol for any given name1.
make-symbol, on the other hand, creates a new symbol every time it is called. These are uninterned symbols -- each one is a completely valid and functional symbol, but not the one which will be seen when you refer to a symbol by its name.
See: C-hig (elisp) Creating Symbols RET
Because defun returns the symbol it sets, you can observe what's going on by capturing the return value and using it as a function:
(defalias 'foo (deftext "ni" "What is the flight speed velocity of a laden swallow?"))
M-x text-ni ;; doesn't work
M-x foo ;; works
or similarly:
(call-interactively (deftext "shrubbery" "It is a good shrubbery. I like the laurels particularly."))
The tricky part in all this -- and the reason that evaluating the expanded form did what you wanted, and yet the macro didn't -- is to do with exactly how and when (or indeed if) the lisp reader translates the name of the function into a symbol.
If we write a function foo1:
(defun foo1 (texttoinsert) (insert-string texttoinsert))
The lisp reader reads that as text, and converts it into a lisp object. We can use read-from-string to do the same thing, and we can look at the printed representation of the resulting lisp object:
ELISP> (car (read-from-string "(defun foo1 (texttoinsert) (insert-string texttoinsert))"))
(defun foo1
(texttoinsert)
(insert-string texttoinsert))
Within that object, the function name is the canonical symbol with the name "foo1". Note, however, that the return value we see from read-from-string is only the printed representation of that object, and the canonical symbol is represented only by its name. The printed representation does not enable us to distinguish between interned and uninterned symbols, as all symbols are represented only by their name.
(Skipping ahead momentarily, this is the source of your issue when evaluating the printed expansion of your macro, as that printed form is passed through the lisp reader, and what was once an uninterned symbol becomes an interned symbol.)
If we then move on to macros:
(defmacro deffoo2 ()
`(defun foo2 (texttoinsert) (insert-string texttoinsert)))
ELISP> (car (read-from-string "(defmacro deffoo2 ()
`(defun foo2 (texttoinsert) (insert-string texttoinsert)))"))
(defmacro deffoo2 nil
`(defun foo2
(texttoinsert)
(insert-string texttoinsert)))
This time the reader has read the macro definition into a lisp object, and within that object is the canonical symbol foo2. We can verify this by inspecting the object directly:
ELISP> (eq 'foo2
(cadr (cadr (nth 3
(car (read-from-string "(defmacro deffoo2 ()
`(defun foo2 () (insert-string texttoinsert)))"))))))
t
So for this macro, it is already dealing with that canonical symbol foo2 before any macro call/expansion happens, because the lisp reader established that when reading the macro itself. Unlike our previous simple function definition (in which the function symbol was determined by the lisp reader as the function was defined), when a macro is called & expanded the lisp reader is not utilised. The macro expansion is performed using pre-existing lisp objects -- no reading is necessary.
In this example the function symbol is already present in the macro, and because it is the canonical symbol we could use (foo2) elsewhere in our code to call that function. (Or, had I made the definition interactive, use M-x foo2.)
Finally getting back to the original macro from the question, it's obvious that the lisp reader never encounters a function name symbol for the function it will define:
ELISP> (car (read-from-string "(defmacro deftext (functionname texttoinsert)
`(defun ,(make-symbol (concatenate 'string \"text-\" functionname)) ()
(interactive)
(insert-string ,texttoinsert)))"))
(defmacro deftext
(functionname texttoinsert)
`(defun ,(make-symbol
(concatenate 'string "text-" functionname))
nil
(interactive)
(insert-string ,texttoinsert)))
Instead this object produced by the lisp reader contains the expression ,(make-symbol (concatenate 'string "text-" functionname)); and that backquoted expression will be evaluated at expansion time to create a new uninterned symbol which will be a part of the object created by that expansion.
In our earlier examples the resulting object had a car of defun (interned), and a cadr of foo1 or foo2 (both also interned).
In this last example, the object has a car of defun (interned) but a cadr of an uninterned symbol (with the name resulting from the concatenate expression).
And finally, if you print that object, the printed representation of that uninterned function symbol will be the symbol name, and reading that printed representation back by evaluating it would cause the function cell for the canonical symbol to be defined instead.
1 In fact the unintern function can be used to unintern a symbol, after which calling intern for the same name would naturally create a new symbol; but that's not important for this discussion.
FWIW, if you use lexical-binding, you don't need to use a macro:
(defun deftext (functionname texttoinsert)
(defalias (intern (concat "text-" functionname))
(lambda ()
(interactive)
(insert-string texttoinsert))))
It's been years, but I think you're probably missing an fset to define the function; see the docs if you are wanting it a compile time too.