How to implement redo statement (as in Perl and Ruby) in Lisp - lisp

Code that requires break statements or continue statements in other languages can be done with block & return-from or catch & throw in Common Lisp and Emacs Lisp. Then there is code that requires redo statements, or at least best written with redo. And redo statements don't have to be about loops. How can I do redo in Lisp?
If there was a redo equivalent in Lisp, I think it would work like this: special form with-redo which takes a symbol and forms, and redo which takes a symbol. The form (with-redo 'foo BODY-FORMS...) may contain (redo 'foo) in its BODY-FORMS, and (redo 'foo) transfers control back to the beginning of BODY-FORMS.

In Common Lisp:
(tagbody
start
(do-something)
(go start))
(dotimes (i some-list)
redo
(when (some-condition-p)
(go redo))
(some-more))

Rainer's answer illustrates the use of tagbody which is probably the easiest way to implement this kind of construct (a particular kind of goto, or unconditional jump). I thought it'd be nice to point out that if you don't want to use an explicit tagbody, or an implicit tagbody provided by one of the standard constructs, you can also create a with-redo just as you suggested. The only difference in this implementation is that we won't quote the tag, since they're not evaluted in tagbody, and being consistent with the other constructs is nice too.
(defmacro with-redo (name &body body)
`(macrolet ((redo (name)
`(go ,name)))
(tagbody
,name
,#body)))
CL-USER> (let ((x 0))
(with-redo beginning
(print (incf x))
(when (< x 3)
(redo beginning))))
1
2
3
; => NIL
Now this is actually a leaky abstraction, since the body could define other labels for the implicit tagbody, and could use go instead of redo, and so on. This might be desirable; lots of the built in iteration constructs (e.g., do, do*) use an implicit tagbody, so it might be OK. But, since you're also adding your own control flow operator, redo, you might want to make sure that it can only be used with tags defined by with-redo. In fact, while Perl's redo can be used with or without a label, Ruby's redo doesn't appear to allow a label. The label-less cases allow behavior of jumping back to the innermost enclosing loop (or, in our case, the innermost with-redo). We can address the leaky abstraction, as well as the ability to nest redos at the same time.
(defmacro with-redo (&body body)
`(macrolet ((redo () `(go #1=#:hidden-label)))
(tagbody
#1#
((lambda () ,#body)))))
Here we've defined a tag for use with with-redo that other things shouldn't know about (and can't find out unless they macroexpand some with-redo forms, and we've wrapped the body in a lambda function, which means that, e.g., a symbol in the body is a form to be evaluated, not a tag for tagbody. Here's an example showing that redo jumps back to the nearest lexically enclosing with-redo:
CL-USER> (let ((i 0) (j 0))
(with-redo
(with-redo
(print (list i j))
(when (< j 2)
(incf j)
(redo)))
(when (< i 2)
(incf i)
(redo))))
(0 0)
(0 1)
(0 2)
(1 2)
(2 2)
; => NIL
Of course, since you can define with-redo on your own, you can make the decisions about which design you want to adopt. Perhaps you like the idea of redo taking no arguments (and disguising a go with a secret label, but with-redo still being an implicit tagbody so that you can define other tags and jump to them with go; you can adapt the code here to do just that, too.
Some notes on implementation
This this answer has generated a few comments, I wanted to make a couple more notes about the implementation. Implementing with-redo with labels is pretty straightfoward, and I think that all the answers posted address it; the label-less case is a bit tricker.
First, the use of a local macrolet is a convenience that will get us warnings with redo is used outside of some lexically enclosing with-redo. E.g., in SBCL:
CL-USER> (defun redo-without-with-redo ()
(redo))
; in: DEFUN REDO-WITHOUT-WITH-REDO
; (REDO)
;
; caught STYLE-WARNING:
; undefined function: REDO
Second, the use of #1=#:hidden-label and #1# means that the go tag for redoing is an uninterned symbol (which lessens the likelihood that the abstraction leaks), but also is the same symbol across expansions of with-redo. In the following snippet tag1 and tag2 are the go-tags from two different expansions of with-redo.
(let* ((exp1 (macroexpand-1 '(with-redo 1 2 3)))
(exp2 (macroexpand-1 '(with-redo a b c))))
(destructuring-bind (ml bndgs (tb tag1 &rest rest)) exp1 ; tag1 is the go-tag
(destructuring-bind (ml bndgs (tb tag2 &rest rest)) exp2
(eq tag1 tag2))))
; => T
An alternative implementation of with-redo that uses a fresh gensym for each macroexpansion does not have this guarantee. For instance, consider with-redo-gensym:
(defmacro with-redo-gensym (&body body)
(let ((tag (gensym "REDO-TAG-")))
`(macrolet ((redo () `(go ,tag)))
(tagbody
,tag
((lambda () ,#body))))))
(let* ((exp1 (macroexpand-1 '(with-redo-gensym 1 2 3)))
(exp2 (macroexpand-1 '(with-redo-gensym a b c))))
(destructuring-bind (ml bndgs (tb tag1 &rest rest)) exp1
(destructuring-bind (ml bndgs (tb tag2 &rest rest)) exp2
(eq tag1 tag2))))
; => NIL
Now, it's worth asking whether this makes a practical difference, and if so, in which cases, and is it a difference for the better or the worse? Quite frankly, I'm not entirely sure.
If you were performing some complicated code manipulation after the inner macroexpansion of an (with-redo ...) form, form1, so that (redo) has already been turned into (go #1#), it means that moving the (go #1#) into the body of another (with-redo ...) form, form2, it will still have the effect of restarting an iteration in form2. In my mind, this makes it more like a return that could be transported from a block b1 into a different block b2, with the only difference it now returns from b2 instead of b1. I think that this is desirable, since we're trying to treat label-less with-redo and redo as primitive control structures.

Update: Emacs 24.4 (soon to be released) has tagbody. cl-lib that comes with Emacs 24.4 includes cl-tagbody.
For a dialect of Lisp which doesn't have tagbody, one can still implement redo as long as the dialect has a catch/throw equivalent.
For Emacs Lisp:
;; with-redo version 0.1
(defmacro with-redo (tag &rest body)
"Eval BODY allowing jumps using `throw'.
TAG is evalled to get the tag to use; it must not be nil.
Then the BODY is executed.
Within BODY, a call to `throw' with the same TAG and a non-nil VALUE causes a jump to the beginning of BODY.
A call to `throw' with the same TAG and nil as VALUE exits BODY and this `with-redo'.
If no throw happens, `with-redo' returns the value of the last BODY form."
(declare (indent 1))
(let ((ret (make-symbol "retval")))
`(let (,ret)
(while
(catch ,tag
(setq ,ret (progn ,#body))
nil))
,ret)))
(defun redo (symbol)
(throw symbol t))
Example of use (all examples are in Emacs Lisp):
(with-redo 'question
(let ((name (read-string "What is your name? ")))
(when (equal name "")
(message "Zero length input. Please try again.")
(beep)
(sit-for 1)
(redo 'question))
name))
Same example written as a mid-test loop instead:
(require 'cl-lib)
(let (name)
(cl-loop do
(setq name (read-string "What is your name? "))
while
(equal name "")
do
(message "Zero length input. Please try again.")
(beep)
(sit-for 1))
name)
Same example written as an infinite loop with a throw instead:
(let (name)
(catch 'question
(while t
(setq name (read-string "What is your name? "))
(unless (equal name "")
(throw 'question name))
(message "Zero length input. Please try again.")
(beep)
(sit-for 1))))
Implementing with-lex-redo-anon and lex-redo, where (lex-redo) causes a jump to the beginning of body of the textually/lexically innermost with-lex-redo-anon form:
;; with-lex-redo-anon version 0.1
(require 'cl-lib)
(defmacro with-lex-redo-anon (&rest body)
"Use with `(lex-redo)'."
(let ((tag (make-symbol "lex-redo-tag"))
(ret (make-symbol "retval")))
`(cl-macrolet ((lex-redo () '(cl-return-from ,tag t)))
(let (,ret)
(while
(cl-block ,tag
(setq ,ret (progn ,#body))
nil))
,ret))))
Example test:
(let ((i 0) (j 0))
(with-lex-redo-anon
(with-lex-redo-anon
(print (list i j))
(when (< j 2)
(incf j)
(lex-redo)))
(when (< i 2)
(incf i)
(lex-redo))))
Same output as in another answer.

Related

Function returns list but prints out NIL in LISP

I'm reading a file char by char and constructing a list which is consist of list of letters of words. I did that but when it comes to testing it prints out NIL. Also outside of test function when i print out list, it prints nicely. What is the problem here? Is there any other meaning of LET keyword?
This is my read fucntion:
(defun read-and-parse (filename)
(with-open-file (s filename)
(let (words)
(let (letter)
(loop for c = (read-char s nil)
while c
do(when (char/= c #\Space)
(if (char/= c #\Newline) (push c letter)))
do(when (or (char= c #\Space) (char= c #\Newline) )
(push (reverse letter) words)
(setf letter '())))
(reverse words)
))))
This is test function:
(defun test_on_test_data ()
(let (doc (read-and-parse "document2.txt"))
(print doc)
))
This is input text:
hello
this is a test
You're not using let properly. The syntax is:
(let ((var1 val1)
(var2 val2)
...)
body)
If the initial value of the variable is NIL, you can abbreviate (varN nil) as just varN.
You wrote:
(let (doc
(read-and-parse "document2.txt"))
(print doc))
Based on the above, this is using the abbreviation, and it's equivalent to:
(let ((doc nil)
(read-and-parse "document2.txt"))
(print doc))
Now you can see that this binds doc to NIL, and binds the variable read-and-parse to "document2.txt". It never calls the function. The correct syntax is:
(let ((doc (read-and-parse "document2.txt")))
(print doc))
Barmar's answer is the right one. For interest, here is a version of read-and-parse which makes possibly-more-idiomatic use of loop, and also abstracts out the 'is the character white' decision since this is something which is really not usefully possible in portable CL as the standard character repertoire is absurdly poor (there's no tab for instance!). I'm sure there is some library available via Quicklisp which deals with this better than the below.
I think this is fairly readable: there's an outer loop which collects words, and an inner loop which collects characters into a word, skipping over whitespace until it finds the next word. Both use loop's collect feature to collect lists forwards. On the other hand, I feel kind of bad every time I use loop (I know there are alternatives).
By default this collects the words as lists of characters: if you tell it to it will collect them as strings.
(defun char-white-p (c)
;; Is a character white? The fallback for this is horrid, since
;; tab &c are not a standard characters. There must be a portability
;; library with a function which does this.
#+LispWorks (lw:whitespace-char-p c)
#+CCL (ccl:whitespacep c) ;?
#-(or LispWorks CCL)
(member char (load-time-value
(mapcan (lambda (n)
(let ((c (name-char n)))
(and c (list c))))
'("Space" "Newline" "Page" "Tab" "Return" "Linefeed"
;; and I am not sure about the following, but, well
"Backspace" "Rubout")))))
(defun read-and-parse (filename &key (as-strings nil))
"Parse a file into a list of words, splitting on whitespace.
By default the words are returned as lists of characters. If
AS-STRINGS is T then they are coerced to strings"
(with-open-file (s filename)
(loop for maybe-word = (loop with collecting = nil
for c = (read-char s nil)
;; carry on until we hit EOF, or we
;; hit whitespace while collecting a
;; word
until (or (not c) ;EOF
(and collecting (char-white-p c)))
;; if we're not collecting and we see
;; a non-white character, then we're
;; now collecting
when (and (not collecting) (not (char-white-p c)))
do (setf collecting t)
when collecting
collect c)
while (not (null maybe-word))
collect (if as-strings
(coerce maybe-word 'string)
maybe-word))))

Rewrite loop as a mapcar

Looking at Practical Common Lisp, we're looking at a simple automated unit test framework. We're trying to write a macro to be used as such:
(check (= (+ 1 2) 3) (= (- 1 4) 9))
This should expand to something using a previously defined function report-result. The suggested implementation is:
(defmacro check (&body forms)
`(progn
,#(loop for f in forms collect `(report-result ,f ',f))))
However, that expansion seems rather procedural to me. I wanted to replace the loop with a mapcar to expand to something like this:
(mapcar #'(lambda (form) (report-result form 'form)) (list form-1 ... form-n))
However, I'm clearly lacking the macro-writing skills to do so. Can someone come up with one such macro?
In case it's relevant, this is the definition of report-result:
(defun report-result (result form)
(format t "~:[FAIL~;pass~] ... ~a~%" result form))
It's indeed fairly simple: you just place the collect expression into the body of your mapcar:
(defmacro check (&body forms)
`(progn
,#(mapcar #'(lambda (form)
`(report-result ,form ',form))
forms)))
You don't really need to know anything about the "macro-y" stuff that's going on, in order to do the replacement you want, which is simply replacing a loop with some other equivalent expression: it will work just as well in a macro context as it would outside.
If you want to expand to a mapcar you can, but there's no real reason to do so, since the list's size is known at compile time. Here's what that would look like:
(defmacro check (&body forms)
`(let ((results (list ,#(mapcar #'(lambda (form)
`(list ,form ',form))
forms))))
(mapcar #'(lambda (result)
(report-result (car result) (cadr result)))
results)))
Which expands like so
> (macroexpand-1 '(check (+ 1 2) (* 2 3)))
(let ((results (list (list (+ 1 2) '(+ 1 2))
(list (* 2 3) '(* 2 3)))))
(mapcar #'(lambda (result) (report-result (car result) (cadr result)))
results))
Which as you can see is rather awkward: the macro already has the forms like (+ 1 2) available to it, but in order to preserve them to runtime for the mapcar lambda to see, you have to emit the input form twice. And you have to produce the whole list to map over, rather than just producing a list that's "finished" to begin with. Additionally, this produces a list as output, and requires having all the inputs and outputs in memory at once: the original macro with progn produced the inputs and outputs one at a time, and discarded them when finished.

Is there an existing lisp macro for building up a list?

In Python, I am able to use yield to build up a list without having to define a temporary variable:
def get_chars_skipping_bar(word):
while word:
# Imperative logic which can't be
# replaced with a for loop.
if word[:3] == 'bar':
word = word[3:]
else:
yield foo[0]
foo = foo[1:]
In elisp, I can't see any way of doing this, either built-in or using any pre-existing libraries. I'm forced to manually build a up a list and call nreverse on it. Since this is a common pattern, I've written my own macro:
(require 'dash)
(require 'cl)
(defun replace-calls (form x func)
"Replace all calls to X (a symbol) in FORM,
calling FUNC to generate the replacement."
(--map
(cond
((consp it)
(if (eq (car it) x)
(funcall func it)
(replace-calls it x func)))
(:else it))
form))
(defmacro with-results (&rest body)
"Execute BODY, which may contain forms (yield foo).
Return a list built up from all the values passed to yield."
(let ((results (gensym "results")))
`(let ((,results (list)))
,#(replace-calls body 'yield
(lambda (form) `(push ,(second form) ,results)))
(nreverse ,results))))
Example usage:
(setq foo "barbazbarbarbiz")
(with-results
(while (not (s-equals? "" foo))
;; Imperative logic which can't be replaced with cl-loop's across.
(if (s-starts-with? "bar" foo)
(setq foo (substring foo 3))
(progn
(yield (substring foo 0 1))
(setq foo (substring foo 1))))))
There must be a better way of doing this, or an existing solution, somewhere in elisp, cl.el, or a library.
The Python function is actually a generator. In ANSI Common Lisp, we would usually reach for a lexical closure to simulate a generator, or else us a library to define generators directly, like Pygen. Maybe these approaches can be ported to Emacs Lisp.
AFAIK, people just use push+nreverse like you do. If you want to define your macro in a more robust way (e.g. so it doesn't misfire on something like (memq sym '(yield stop next))) you could do it as:
(defmacro with-results (&rest body)
"Execute BODY, which may contain forms (yield EXP).
Return a list built up from all the values passed to `yield'."
(let ((results (gensym "results")))
`(let ((,results '()))
(cl-macrolet ((yield (exp) `(push ,exp ,results)))
,#body)
(nreverse ,results))))
Maybe something like this:
(setq foo "barbaz")
(cl-loop for i from 0 to (1- (length foo))
collect (string (aref foo i)))
In any case, there's nothing wrong with push and nreverse.
Lisp is different from Python. yield is not used. I also see the use of coroutine-like constructs for this as a mistake. It's the equivalent of the come-from construct. Suddenly routines have multiple context dependent entry points.
In Lisp use functions/closures instead.
In Common Lisp, the LOOP macro allows efficient mappings over vectors. The following code can be abstracted to some mapping function, if preferred:
CL-USER 17 > (defun chars-without-substring (string substring)
(loop with i = 0
while (< i (length string))
when (and (>= (- (length string) i) (length substring))
(string= substring string
:start2 i
:end2 (+ i (length substring))))
do (incf i (length substring))
else
collect (prog1 (char string i) (incf i))))
CHARS-WITHOUT-SUBSTRING
CL-USER 18 > (chars-without-substring "barbazbarbarbiz" "bar")
(#\b #\a #\z #\b #\i #\z)

Function name and dynamic binding in Common Lisp

I'm reading Peter Norvig's Paradigms of AI. In chapter 6.2, the author uses code like below (not the original code, I picked out the troubling part):
Code Snippet:
(progv '(op arg) '(1+ 1)
(eval '(op arg)))
As the author's original intent, this code should return 2, but in sbcl 1.1.1, the interpreter is apparently not looking up op in the environment, throwing out op: undefined function.
Is this implementation specific? Since the code must have been tested on some other lisp.
p.s Original code
You probably mean
(progv '(op arg) '(1+ 1)
(eval '(funcall op arg)))
Edit(2013-08-21):
PAIP was written in pre-ANSI-Common-Lisp era, so it's possible the code
there contains a few noncompliances wrt the standard. We can make
the examples work with the following revision:
(defun match-if (pattern input bindings)
"Test an arbitrary expression involving variables.
The pattern looks like ((?if code) . rest)."
(and (eval (reduce (lambda (code binding)
(destructuring-bind (var . val) binding
(subst val var code)))
bindings :initial-value (second (first pattern))))
(pat-match (rest pattern) input bindings)))
;; CL-USER> (pat-match '(?x ?op ?y is ?z (?if (eql (?op ?x ?y) ?z))) '(3 + 4 is 7))
;; ((?Z . 7) (?Y . 4) (?OP . +) (?X . 3) (T . T))
;; CL-USER> (pat-match '(?x ?op ?y (?if (?op ?x ?y))) '(3 > 4))
;; NIL
Elements in first positions are not looked up as values, but as functions and there is no concept of dynamic binding in the function namespace.
I'd say after a quick look that the original code was designed to evaluate in a context like
(progv '(x y) '(12 34)
(eval '(> (+ x y) 99)))
i.e. evaluating a formula providing substitution for variables, not for function names.
The other answers so far are right, in that the actual form being evaluated is not the variables being bound by progv (simply (op arg)), but none have mentioned what is being evaluated. In fact, the comments in the code you linked to provide a (very) short explanation (this is the only code in that file that uses progv):
(defun match-if (pattern input bindings)
"Test an arbitrary expression involving variables.
The pattern looks like ((?if code) . rest)."
;; *** fix, rjf 10/1/92 (used to eval binding values)
(and (progv (mapcar #'car bindings)
(mapcar #'cdr bindings)
(eval (second (first pattern))))
(pat-match (rest pattern) input bindings)))
The idea is that a call to match-if gets called like
(match-if '((?if code) . rest) input ((v1 val1) (v2 val2) ...))
and eval is called with (second (first pattern)), which the value of code. However, eval is called within the progv that binds v1, v2, &c., to the corresponding val1, val2, &c., so that if any of those variables appear free in code, then they are bound when code is evaluated.
Problem
The problem that I see here is that, by the code we can't tell if the value is to be saved as the variable's symbol-value or symbol-function. Thus when you put a + as a value to some corresponding variable, say v, then it'll always be saved as the symbol-value of var, not it's symbol-function.
Therefore when you'll try to use it as, say (v 1 2) , it won't work. Because there is no function named v in the functions' namespace(see this).
So, what to do?
A probable solution can be explicit checking for the value that is to be bound to a variable. If the value is a function, then it should be bound to the variable's function value. This checking can be done via fboundp.
So, we can make a macro functioner and a modified version of match-if. functioner checks if the value is a function, and sets it aptly. match-if does the dynamic local bindings, and allows other code in the scope of the bound variables.
(defmacro functioner (var val)
`(if (and (symbolp ',val)
(fboundp ',val))
(setf (symbol-function ',var) #',val)
(setf ,var ,val)))
(defun match-if (pattern input bindings)
(eval `(and (let ,(mapcar #'(lambda (x) (list (car x))) bindings)
(declare (special ,# (mapcar #'car bindings)))
(loop for i in ',bindings
do (eval `(functioner ,(first i) ,(rest i))))
(eval (second (first ',pattern))))
(pat-match (rest ',pattern) ',input ',bindings))))

Emacs cond, possible to have things happen between clauses?

I programmed some months ago some code with a lot of if statements. If region-active-p, if beginning-of-line, those kind of things.
Having learned about the cond lisp, I was wondering if I could improve my code a lot.
The problem is that this cond is only doing things when "true" as far as I see it, while I actually need the move back-to-indentation in between these checks.
In order to properly skip the last clause, I even have to set variable values.
(defun uncomment-mode-specific ()
"Uncomment region OR uncomment beginning of line comment OR uncomment end"
(interactive)
(let ((scvar 0) (scskipvar 0))
(save-excursion
(if (region-active-p)
(progn (uncomment-region (region-beginning) (region-end))
(setq scskipvar 1))
(back-to-indentation)) ; this is that "else" part that doesn't fit in cond
(while (string= (byte-to-string (following-char)) comment-start)
(delete-char 1)
(setq scskipvar 1))
(indent-for-tab-command)
(when (= scskipvar 0)
(search-forward comment-start nil t)
(backward-char 1)
(kill-line))
)))
)
So basically my question is, I would kind of like to have some consequences of not giving "true" to a clause, before the check of another clause. Is this possible? If not, what would be the best thing to do?
EDIT: Since we are using this as the example case for a solution, I wrote it down so it is easier to understand.
If region is active, remove comments from region. If not, move point to intendation.
For as long as the following character is a comment character, delete it. Afterwards, indent this line.
If it didn't do any of the above, search forward for a comment character, and kill that line.
(defun delete-on-this-line (regex)
(replace-regexp regex "" nil (line-beginning-position) (line-end-position)))
(defun delete-leading-comment-chars ()
(delete-on-this-line (eval `(rx bol (* space) (group (+ ,comment-start))))))
(defun delete-trailing-comment-chars ()
(delete-on-this-line (eval `(rx (group (+ ,comment-end)) (* space) eol))))
(defun delete-trailing-comment ()
(delete-on-this-line (eval `(rx (group (+ ,comment-start) (* anything) eol)))))
(defun uncomment-dwim ()
(interactive)
(save-excursion
(if (region-active-p)
(uncomment-region (region-beginning) (region-end))
(or (delete-leading-comment-chars)
(delete-trailing-comment-chars)
(delete-trailing-comment)))))
Edit: A little explanation:
It's a lot easier to do regex replacements than manage loops to do deletion, so that gets rid of the state. And the steps are all mutually exclusive, so you can just use or for each option.
The rx macro is a little DSL that compiles down to valid regexes, and it's also amenable to lispy syntax transforms, so I can dynamically build a regex using the comment chars for the current mode.
(defmacro fcond (&rest body)
(labels ((%substitute-last-or-fail
(new old seq)
(loop for elt on seq
nconc
(if (eql (car elt) old)
(when (cdr elt)
(error "`%S' must be the last experssion in the clause"
(car elt)))
(list new)
(list (car elt))))))
(loop with matched = (gensym)
with catcher = (gensym)
for (head . rest) in body
collect
`(when (or ,head ,matched)
(setq ,matched t)
,#(%substitute-last-or-fail `(throw ',catcher nil) 'return rest))
into clauses
finally
(return `(let (,matched) (catch ',catcher ,#clauses))))))
(macroexpand '(fcond
((= 1 2) (message "1 = 2"))
((= 1 1) (message "1 = 1"))
((= 1 3) (message "1 = 3") return)
((= 1 4) (message "1 = 4"))))
(let (G36434)
(catch (quote G36435)
(when (or (= 1 2) G36434)
(setq G36434 t)
(message "1 = 2"))
(when (or (= 1 1) G36434)
(setq G36434 t)
(message "1 = 1"))
(when (or (= 1 3) G36434)
(setq G36434 t)
(message "1 = 3")
(throw (quote G36435) nil))
(when (or (= 1 4) G36434)
(setq G36434 t)
(message "1 = 4"))))
Here's something quick to do, what I think you may be after, i.e. something that would mimic the behaviour switch in C.
The idea is that all clauses are tested sequentially for equality, and if one matches, then all following clauses are executed, until the return keyword (it would be break in C, but Lisp uses return for the similar purpose in the loop, so I thought that return would be better). The code above thus will print:
1 = 1
1 = 3
Technically, this is not how switch works in C, but it will produce the same effect.
One thing I did here for simplicity, which you want to avoid / solve differently - the use of return keyword, you probably want to impose stricter rules on how it should be searched for.
cond
Cond evaluates a series of conditions in a list, each item in a list can be a condition, and then executable instructions.
The example in the Emacs Lisp manual is adequate to demonstrate how it works, I've annotated it here to help you understand how it works.
(cond ((numberp x) x) ;; is x a number? return x
((stringp x) x) ;; is x a string? return x
((bufferp x) ;; is x a buffer?
(setq temporary-hack x) ;; set temporary-hack to buffer x
(buffer-name x)) ;; return the buffer-name for buffer x
((symbolp x) (symbol-value x))) ;; is x a symbol? return the value of x
Each part of the condition can be evaluated any way you like, the fact x above is in each condition is coincidental.
For example:
(cond ((eq 1 2) "Omg equality borked!") ;; Will never be true
(t "default")) ;; always true
So comparisons with switch are a bit limited, it's essentially a list of if statements, that executes/returns the first true condition's body list.
Hopefully this helps you understand cond a bit better.
(cond (condition body ... ) ;; execute body of 1st passing
(condition body ... ) ;; condition and return result
(condition body ... ) ;; of the final evaluation.
;; etc
)
OR
You can do things similar to switch with OR, depending on how you structure the code.
This isn't functional style, because it relies on side-effects to do what you want, then returns a boolean value for flow control, here's an example in pseudo lisp.
(or)
(or
(lambda() (do something)
(evaluate t or nil) ; nil to continue; t to quit.
)
(lambda() (do something)
(evaluate t or nil) ; nil to continue; t to quit.
)
(lambda() (do something)
(evaluate t or nil) ; nil to continue; t to quit.
)
(lambda() (do something)
(evaluate t or nil) ; nil to continue; t to quit.
)
)
Here's working example of a switch like structure using or
(or
(when (= 1 1)
(progn
(insert "hello\n")
nil))
(when (= 1 2) ;; condition fails.
(progn
(insert "hello\n")
nil)) ;; returns false (nil)
(when (= 1 1)
(progn
(insert "hello\n")
t)) ;; returns true, so we bail.
(when (= 1 1)
(progn
(insert "hello\n")
nil))
)
Inserts :
hello
hello
(and)
The and operator (not just in Lisp) is also very useful, instead of evaluating everything until true, it evaluates conditions that are true, until a false is evaluated.
Both or & and can be used to build useful logic trees.
This is how I did it now according to Chris' idea that breaking it down into seperate functions would make it easier.
EDIT: Now also applied the or knowledge gained in this thread gained from Slomojo (no more variables!)
(defun sc-uncomment ()
(interactive)
(or
(if (region-active-p)
(uncomment-region (region-beginning) (region-end))
(back-to-indentation)
nil)
(if (string= (byte-to-string (following-char)) comment-start)
(sc-check-start)
(sc-end))))
(defun sc-check-start ()
(interactive)
(while (string= (byte-to-string (following-char)) comment-start)
(delete-char 1))
)
(defun sc-end ()
(interactive)
(search-forward comment-start nil t)
(backward-char 1)
(kill-line))
)