From: Michiel Borkent
Subject: Which form do you prefer (and why)?
Date: 
Message-ID: <a58e8f47.0410180210.4e2f2a9@posting.google.com>
Form 1:

(defun one-or-another (fun1 fun2 x)
  (if (zerop (mod (get-internal-real-time) 2))
    (funcall fun1 x x)
    (funcall fun2 x x)))

Form 2:

(defun one-or-another (fun1 fun2 x)
  (funcall 
   (if (zerop (mod (get-internal-real-time) 2))
     fun1 fun2)
     x x))

(one-or-another #'* #'+ 4)
=> sometimes 8, sometimes 16

Grtz,
Michiel

From: Mikael Brockman
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <87y8i49v8y.fsf@igloo.phubuh.org>
··············@gmail.com (Michiel Borkent) writes:

> Form 1:
> 
> (defun one-or-another (fun1 fun2 x)
>   (if (zerop (mod (get-internal-real-time) 2))
>     (funcall fun1 x x)
>     (funcall fun2 x x)))
> 
> Form 2:
> 
> (defun one-or-another (fun1 fun2 x)
>   (funcall 
>    (if (zerop (mod (get-internal-real-time) 2))
>      fun1 fun2)
>      x x))
> 
> (one-or-another #'* #'+ 4)
> => sometimes 8, sometimes 16

I prefer

| (defun one-or-another (fun1 fun2 x)
|   (let ((function
|          (if (zerop (mod (get-internal-real-time) 2))
|              fun1
|            fun2)))
|     (funcall function x x)))

because nesting the IF in the FUNCALL confuses me, and repeating
``(funcall ... x x)'' annoys me.
From: Jock Cooper
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <m3wtxnzyvp.fsf@jcooper02.sagepub.com>
Mikael Brockman <······@phubuh.org> writes:

> ··············@gmail.com (Michiel Borkent) writes:
> 
> > Form 1:
> > 
> > (defun one-or-another (fun1 fun2 x)
> >   (if (zerop (mod (get-internal-real-time) 2))
> >     (funcall fun1 x x)
> >     (funcall fun2 x x)))
> > 
> > Form 2:
> > 
> > (defun one-or-another (fun1 fun2 x)
> >   (funcall 
> >    (if (zerop (mod (get-internal-real-time) 2))
> >      fun1 fun2)
> >      x x))
> > 
> > (one-or-another #'* #'+ 4)
> > => sometimes 8, sometimes 16
> 
> I prefer
> 
> | (defun one-or-another (fun1 fun2 x)
> |   (let ((function
> |          (if (zerop (mod (get-internal-real-time) 2))
> |              fun1
> |            fun2)))
> |     (funcall function x x)))
> 
> because nesting the IF in the FUNCALL confuses me, and repeating
> ``(funcall ... x x)'' annoys me.

I tend to agree here.  

Also, I wrote some code awhile back to handle this sort of thing
more generically:

(defmacro fixed-random-generator (events &key (default :default))
  "Events is ((eventkw1 percent1) (eventkw2 percent2) ...).
   Percents should add up to more than 100 -- if less a default case 
      (specify with default kw) will be chosen.
   return is the eventkw chosen.  See test-fixed-random-generator for example"
  (flet ((%frg-cond-generator ()
	   (loop for (event percentage) in events
		 with low-end = 0 
		 collect `((<= ,low-end rnd ,(+ low-end percentage)) ,event) into forms
		 do (setq low-end (+ 1 low-end percentage))
		 finally (return (nconc forms `((t ,default)))))))
    `(let ((rnd (random 100)))
      (cond ,@(%frg-cond-generator)))))

(defun test-fixed-random-generator (&optional (iter 10000))
  (let ((result-hash (make-hash-table)))
    (dotimes (i iter)
      (let* ((item (fixed-random-generator ((:item-1 10) (:item-2 5) 
                                            (:foo 1) (:bar 2)) :default :haha))
	     (current (gethash item result-hash 1)))
	(setf (gethash item result-hash) (1+ current))))
    (loop for key being each hash-key in result-hash
	  using (hash-value count)
	  do (format t "~a = ~a~%" key count))))

(defmacro variable-random-generator (events &key (default :default))
  "Like fixed-random-generator, except events is (eventkw1 eventkw2 ...) 
      and the return is a lambda--
   the lambda takes as args the percent values for the keywords specified.
   See test-variable-random-generator for example"
  (flet ((%vrg-get-lambda-args () 
	   (loop for event in events
		 collect (gensym (symbol-name event))))
	 (%vrg-get-computed-ranges (syms)
	   (loop for sym in syms
		 with last
		 for gsym = (gensym)
		 collect `(,gsym (+ ,sym ,(or last 0)))
		 do (setq last gsym)))
	 (%vrg-cond-generator (event-pairs)
	   (loop for (event percentage) in event-pairs
		 with low-end = 0 
		 collect `((<= ,low-end rnd ,percentage) ,event) into forms
		 do (setq low-end `(1+ ,percentage))
		 finally (return (nconc forms `((t ,default)))))))
    (let* ((%args (%vrg-get-lambda-args))
	   (%computed (%vrg-get-computed-ranges %args))
	   (%events (loop for event in events
			  for (sym nil) in %computed
			  collect (list event sym)))
	   )
      `(lambda ,%args
	(let* ((rnd (random 100))
	       ,@%computed)
	  (cond ,@(%vrg-cond-generator %events)))))))

(defun test-variable-random-generator (&optional (iter 10000))
  (let ((result-hash (make-hash-table))
	(the-fn (variable-random-generator (:item-1 :item-2 
                                            :foo :bar) :default :haha)))
    (dotimes (i iter)
      (let* ((item (funcall the-fn 10 5 1 2))
	     (current (gethash item result-hash 1)))
	(setf (gethash item result-hash) (1+ current))))
    (loop for key being each hash-key in result-hash
	  using (hash-value count)
	  do (format t "~a = ~a~%" key count))))



--
Jock Cooper
www.fractal-recursions.com
From: Pascal Bourguignon
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <87y8i42udm.fsf@thalassa.informatimago.com>
··············@gmail.com (Michiel Borkent) writes:

> Form 1:
> 
> (defun one-or-another (fun1 fun2 x)
>   (if (zerop (mod (get-internal-real-time) 2))
>     (funcall fun1 x x)
>     (funcall fun2 x x)))
> 
> Form 2:
> 
> (defun one-or-another (fun1 fun2 x)
>   (funcall 
>    (if (zerop (mod (get-internal-real-time) 2))
>      fun1 fun2)
>      x x))
> 
> (one-or-another #'* #'+ 4)
> => sometimes 8, sometimes 16

Usually, I choose the second form.
Also for example in: (push item (if condition list1 list2))

The reason why is that usualy it leads to more concise code, therefore
clearer code. (But that may not always be the case).

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

Voting Democrat or Republican is like choosing a cabin in the Titanic.
From: Lars Brinkhoff
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <85pt3gcnv5.fsf@junk.nocrew.org>
Pascal Bourguignon <····@mouse-potato.com> writes:
> Also for example in: (push item (if condition list1 list2))

Have you redefined if to be setf-able?

-- 
Lars Brinkhoff,         Services for Unix, Linux, GCC, HTTP
Brinkhoff Consulting    http://www.brinkhoff.se/
From: David Steuber
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <873c0b9a9g.fsf@david-steuber.com>
Lars Brinkhoff <·········@nocrew.org> writes:

> Pascal Bourguignon <····@mouse-potato.com> writes:
> > Also for example in: (push item (if condition list1 list2))
> 
> Have you redefined if to be setf-able?

Doesn't the fact that list1 and list2 is setf-able take care of that?

-- 
An ideal world is left as an excercise to the reader.
   --- Paul Graham, On Lisp 8.1
From: Kaz Kylheku
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <cf333042.0410181359.251e0096@posting.google.com>
David Steuber <·····@david-steuber.com> wrote in message news:<··············@david-steuber.com>...
> Lars Brinkhoff <·········@nocrew.org> writes:
> 
> > Pascal Bourguignon <····@mouse-potato.com> writes:
> > > Also for example in: (push item (if condition list1 list2))
> > 
> > Have you redefined if to be setf-able?
> 
> Doesn't the fact that list1 and list2 is setf-able take care of that?

No. The property of being a generalized place does not automatically
propagate through arbitrary nested expressions. The HyperSpec states
which standard function forms denote places. Additionally, it must be
possible to use places that are wrapped in THE, VALUES or certain
APPLY uses.

If the above works, it's probably because the implementation has a
SETF expander for IF. This is the case with CLISP for instance:

[18]> (get-setf-expansion '(if x y z))
(#:G389) ;
(X) ;
(#:G390) ;
(IF #:G389 (SETQ Y #:G390) (SETQ Z #:G390)) ;
(IF #:G389 Y Z)

[19]> (symbol-plist 'if)
(SYSTEM::SETF-EXPANDER (-5 . #<COMPILED-CLOSURE #:SETF-IF>))

I can't find a requirement for the existence of this, so it looks like
an extension.

See 5.1.2 Kinds of Places.
From: Karl A. Krueger
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <cl162v$pk$1@baldur.whoi.edu>
David Steuber <·····@david-steuber.com> wrote:
> Lars Brinkhoff <·········@nocrew.org> writes:
>> Pascal Bourguignon <····@mouse-potato.com> writes:
>> >
>> > Also for example in: (push item (if condition list1 list2))
>> 
>> Have you redefined if to be setf-able?
> 
> Doesn't the fact that list1 and list2 is setf-able take care of that?

CLISP accepts it.  SBCL does not, giving this:


; in: LAMBDA NIL
;     (FUNCALL #'(SETF IF) #:G3790 #:G3793 #:G3792 #:G3791)
; ==>
;   (SB-C::%FUNCALL #'(SETF IF) #:G3790 #:G3793 #:G3792 #:G3791)
;
; caught WARNING:
;   The function (SETF IF) is undefined, and its name is reserved by ANSI CL so
;   that even if it it were defined later, the code doing so would not be portable.

;
; caught STYLE-WARNING:
;   This function is undefined:
;     (SETF IF)
;
; compilation unit finished
;   caught 1 WARNING condition
;   caught 1 STYLE-WARNING condition

debugger invoked on a UNDEFINED-FUNCTION in thread 20953:
  The function (SETF IF) is undefined.


-- 
Karl A. Krueger <········@example.edu> { s/example/whoi/ }

Every program has at least one bug and can be shortened by at least one line.
By induction, every program can be reduced to one line which does not work.
From: Kenny Tilton
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <zSVcd.82626$Ot3.53894@twister.nyc.rr.com>
Karl A. Krueger wrote:
> David Steuber <·····@david-steuber.com> wrote:
> 
>>Lars Brinkhoff <·········@nocrew.org> writes:
>>
>>>Pascal Bourguignon <····@mouse-potato.com> writes:
>>>
>>>>Also for example in: (push item (if condition list1 list2))
>>>
>>>Have you redefined if to be setf-able?
>>
>>Doesn't the fact that list1 and list2 is setf-able take care of that?
> 
> 
> CLISP accepts it.  SBCL does not, giving this:
> 
> 
> ; in: LAMBDA NIL
> ;     (FUNCALL #'(SETF IF) #:G3790 #:G3793 #:G3792 #:G3791)
> ; ==>
> ;   (SB-C::%FUNCALL #'(SETF IF) #:G3790 #:G3793 #:G3792 #:G3791)
> ;
> ; caught WARNING:
> ;   The function (SETF IF) is undefined, and its name is reserved by ANSI CL so
> ;   that even if it it were defined later, the code doing so would not be portable.
> 
> ;
> ; caught STYLE-WARNING:
> ;   This function is undefined:
> ;     (SETF IF)
> ;
> ; compilation unit finished
> ;   caught 1 WARNING condition
> ;   caught 1 STYLE-WARNING condition
> 
> debugger invoked on a UNDEFINED-FUNCTION in thread 20953:
>   The function (SETF IF) is undefined.
> 
> 

AllegroCL gives macroexpansion:

(LET* ((#:G1004 ITEM)
        (#:G1001 CONDITION)
        (#:G1002 LIST1)
        (#:G1003 LIST2)
        (#:G1000 (CONS #:G1004 (IF #:G1001 #:G1002 #:G1003))))
   (FUNCALL #'(SETF IF) #:G1000 #:G1001 #:G1002 #:G1003))

...and runtime error:

Error: `(SETF IF)' is not fbound
[condition type: UNDEFINED-FUNCTION]

kt

-- 
Cells? Cello? Celtik?: http://www.common-lisp.net/project/cells/
Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film
From: Pascal Bourguignon
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <87pt3f3o3z.fsf@thalassa.informatimago.com>
Lars Brinkhoff <·········@nocrew.org> writes:

> Pascal Bourguignon <····@mouse-potato.com> writes:
> > Also for example in: (push item (if condition list1 list2))
> 
> Have you redefined if to be setf-able?

No. But it works.

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

Voting Democrat or Republican is like choosing a cabin in the Titanic.
From: Kalle Olavi Niemitalo
Subject: SETF-able IF (was: Which form do you prefer (and why)?)
Date: 
Message-ID: <87wtxny88x.fsf_-_@Astalo.kon.iki.fi>
Pascal Bourguignon <····@mouse-potato.com> writes:

> Lars Brinkhoff <·········@nocrew.org> writes:
>
>> Pascal Bourguignon <····@mouse-potato.com> writes:
>> > Also for example in: (push item (if condition list1 list2))
>> 
>> Have you redefined if to be setf-able?
>
> No. But it works.

Which implementation are you using, and what does
(get-setf-expansion (if condition list1 list2)) return?
SBCL 0.8.14.9 just signals an error:

* (let (a b c d)
    (push a (if b c d)))
; [ominous warnings omitted]
debugger invoked on a UNDEFINED-FUNCTION in thread 5898:
  The function (SETF IF) is undefined.

I've been playing with SETF lately, so here's my attempt.

(defmacro setfable-if (test then else)
  `(if ,test ,then ,else))

(define-setf-expander setfable-if (test then else &environment env)
  (multiple-value-bind (then-vars then-vals then-stores then-write then-read)
      (get-setf-expansion then env)
    (multiple-value-bind (else-vars else-vals else-stores else-write else-read)
        (get-setf-expansion else env)
      (let ((test-var (gensym "TEST"))
            (if-stores (loop repeat (max (length then-stores)
                                         (length else-stores))
                             collect (gensym "STORE"))))
        (flet ((storing-form-half (inner-stores inner-write)
                 ;; This could use just LET, but perhaps
                 ;; MULTIPLE-VALUE-BIND makes it clearer that the
                 ;; variables hold a set of multiple values.
                 `(multiple-value-bind (,@inner-stores)
                      (values ,@if-stores)
                    ,inner-write
                    ;; Per 5.1.1.2, the storing form of the setf
                    ;; expansion must return the values of the store
                    ;; variables.  See if INNER-WRITE already did that.
                    ,@(unless (= (length inner-stores) (length if-stores))
                        `((values ,@if-stores))))))
          (values `(,test-var ,@then-vars ,@else-vars)
                  `(,test
                    ,@(loop for then-val in then-vals
                            collect `(when ,test-var ,then-val))
                    ,@(loop for else-val in else-vals
                            collect `(unless ,test-var ,else-val)))
                  if-stores
                  `(if ,test-var
                       ,(storing-form-half then-stores then-write)
                       ,(storing-form-half else-stores else-write))
                  `(if ,test-var ,then-read ,else-read)))))))

With the implementation above, (setf (setfable-if (a) (b (c) (d))
(e (f) (g))) (h)) expands to something like this:

  (let* ((#:test3880 (a))
         (#:g3876 (when #:test3880 (c)))
         (#:g3875 (when #:test3880 (d)))
         (#:g3879 (unless #:test3880 (f)))
         (#:g3878 (unless #:test3880 (g))))
    ...)

That is, there are (+ (length then-vars) (length else-vars))
temporary variables in total; half of them are unused.  It might
be possible to reduce the number to (max (length then-vars)
(length else-vars)), though getting the scopes right is tricky:

  (let* ((#:test3880 (a))
         (#:g3882 (if #:test3880 (c) (f)))
         (#:g3883 (if #:test3880
                    (symbol-macrolet ((#:g3876 #:g3882)) (d))
                    (symbol-macrolet ((#:g3879 #:g3882)) (g)))))
    ...)

I'm not sure this contraption would work with all possible inner
setf expansions.  Can you find any corner cases?

It bothers me that the storing form cannot return a variable
number of values.

Perhaps the ELSE form should default to (values).
From: Kalle Olavi Niemitalo
Subject: Re: SETF-able IF
Date: 
Message-ID: <87pt3fy4kr.fsf@Astalo.kon.iki.fi>
I peeked at the IF setf expander of CLISP 2.33.2, in
src/places.lisp.  It's pretty similar to mine, except:

- It signals an error if the true and false branches accept
  different numbers of values (by having different numbers of
  store variables in their setf expansions).  This resolves the
  question of how many values to return from the storing form.

- It uses MAPCAR rather than LOOP.

- It outputs IF and IF NOT, rather than WHEN and UNLESS.

- It does not generate new store variables for the IF form and
  bind the store variables of the branches to their values.
  Instead, it uses the store variables of the true branch
  directly as the store variables of the IF form, and tweaks the
  storing form of the false branch with SUBLIS so that it too
  refers to the same variables.  The former optimization is OK
  as there is always the correct number of variables, but the
  latter optimization means the setf expander can be fooled by
  hiding a variable reference somewhere SUBLIS doesn't look:

    (defmacro unvector (v) (aref v 0))

    (defmacro same (x) x)
    (define-setf-expander same (x) ; assumes X is a plain variable
      (let ((g (gensym)))
        (values '() '() `(,g) `(unvector #((setq ,x ,g))) x)))

    (get-setf-expansion '(if nil var (same var)))
    ;; => (#:G5038) ;
    ;;    (NIL) ;
    ;;    (#:G5039) ;
    ;;    (IF #:G5038 (SETQ VAR #:G5039) (UNVECTOR #((SETQ VAR #:G5040)))) ;
    ;;    (IF #:G5038 VAR VAR)

  Here, the store variable #:G5040 has originally been generated
  for the setf expansion of (same var).  The setf expander of IF
  has replaced that with #:G5039 but failed to update the vector.

  Another problem with SUBLIS is that it may break the sharing of
  subtrees.  If the input is (eq '#1=(#:G5040) '#1#), the output
  might be (eq '(#1=#:G5039) '(#1#)) which is no longer true.
  I'd be surprised if this mattered in an actual setf expansion,
  though.

  I'm still not sure SYMBOL-MACROLET is entirely reliable for
  redirecting variables of setf expansions, but at least it would
  handle these cases correctly.
From: Mikael Brockman
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <87sm8bao4o.fsf@igloo.phubuh.org>
Lars Brinkhoff <·········@nocrew.org> writes:

> Pascal Bourguignon <····@mouse-potato.com> writes:
> > Also for example in: (push item (if condition list1 list2))
> 
> Have you redefined if to be setf-able?

You don't need SETF for PUSH -- only RPLACA and RPLACD.

| (defun push (element cons)
|   (let ((old-cons (cons (car cons)
|                         (cdr cons))))
|     (rplaca cons element)
|     (rplacd cons old-cons)))
From: Peter Seibel
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <m3pt3fkhq9.fsf@javamonkey.com>
Mikael Brockman <······@phubuh.org> writes:

> Lars Brinkhoff <·········@nocrew.org> writes:
>
>> Pascal Bourguignon <····@mouse-potato.com> writes:
>> > Also for example in: (push item (if condition list1 list2))
>> 
>> Have you redefined if to be setf-able?
>
> You don't need SETF for PUSH -- only RPLACA and RPLACD.
>
> | (defun push (element cons)
> |   (let ((old-cons (cons (car cons)
> |                         (cdr cons))))
> |     (rplaca cons element)
> |     (rplacd cons old-cons)))


Not quite. Try this with your version of PUSH:

  (let ((x ())) (push 10 x) x)

-Peter


-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Mikael Brockman
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <87oeizamjm.fsf@igloo.phubuh.org>
Peter Seibel <·····@javamonkey.com> writes:

> Mikael Brockman <······@phubuh.org> writes:
> 
> > Lars Brinkhoff <·········@nocrew.org> writes:
> >
> >> Pascal Bourguignon <····@mouse-potato.com> writes:
> >> > Also for example in: (push item (if condition list1 list2))
> >> 
> >> Have you redefined if to be setf-able?
> >
> > You don't need SETF for PUSH -- only RPLACA and RPLACD.
> >
> > | (defun push (element cons)
> > |   (let ((old-cons (cons (car cons)
> > |                         (cdr cons))))
> > |     (rplaca cons element)
> > |     (rplacd cons old-cons)))
> 
> 
> Not quite. Try this with your version of PUSH:
> 
>   (let ((x ())) (push 10 x) x)

Oops.  Of course.  You do need SETF.
From: Thomas A. Russ
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <ymi4qkracrn.fsf@sevak.isi.edu>
··············@gmail.com (Michiel Borkent) writes:

> 
> Form 1:
> 
> (defun one-or-another (fun1 fun2 x)
>   (if (zerop (mod (get-internal-real-time) 2))
>     (funcall fun1 x x)
>     (funcall fun2 x x)))

I prefer this one, since the structure of the code is a bit clearer to
me.

Of course, I do wonder why you don't use (zerop (random 2)) for the test
instead of GET-INTERNAL-REAL-TIME.  There's nothing that assures you the
implementation's lowest order bit on real time won't always be ZERO.

> 
> Form 2:
> 
> (defun one-or-another (fun1 fun2 x)
>   (funcall 
>    (if (zerop (mod (get-internal-real-time) 2))
>      fun1 fun2)
>      x x))
> 
> (one-or-another #'* #'+ 4)
> => sometimes 8, sometimes 16
> 
> Grtz,
> Michiel





Thomas A. Russ,  USC/Information Sciences Institute
From: Marco Antoniotti
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <KUUcd.18$u5.32579@typhoon.nyu.edu>
Hi

I prefer the first one.  Call it left over from imperative languages, 
but I think "expression" IFs should be used sparingly.

Besides, I find it easier to read in an anglicized form.

Cheers
--
Marco


Michiel Borkent wrote:

> Form 1:
> 
> (defun one-or-another (fun1 fun2 x)
>   (if (zerop (mod (get-internal-real-time) 2))
>     (funcall fun1 x x)
>     (funcall fun2 x x)))
> 
> Form 2:
> 
> (defun one-or-another (fun1 fun2 x)
>   (funcall 
>    (if (zerop (mod (get-internal-real-time) 2))
>      fun1 fun2)
>      x x))
> 
> (one-or-another #'* #'+ 4)
> => sometimes 8, sometimes 16
> 
> Grtz,
> Michiel
From: Philip Haddad
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <ba57c4f9.0410181554.4e69440f@posting.google.com>
··············@gmail.com (Michiel Borkent) wrote in message news:<···························@posting.google.com>...
> Form 1:
> 
> (defun one-or-another (fun1 fun2 x)
>   (if (zerop (mod (get-internal-real-time) 2))
>     (funcall fun1 x x)
>     (funcall fun2 x x)))
> 
> Form 2:
> 
> (defun one-or-another (fun1 fun2 x)
>   (funcall 
>    (if (zerop (mod (get-internal-real-time) 2))
>      fun1 fun2)
>      x x))
> 
> (one-or-another #'* #'+ 4)
> => sometimes 8, sometimes 16
> 
> Grtz,
> Michiel


I prefer form 1, however, I think it would be better to create a
lambda function and funcall that. I mean the lambda should hold the
fun1 fun2 stuff. I'm not really sure why I think that though, so if
there is a resounding reason I shouldn't let me know.

--
Certum quod factum
Philip Haddad
From: Barry Margolin
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <barmar-242366.20225218102004@comcast.dca.giganews.com>
In article <···························@posting.google.com>,
 ··············@gmail.com (Michiel Borkent) wrote:

> Form 1:
> 
> (defun one-or-another (fun1 fun2 x)
>   (if (zerop (mod (get-internal-real-time) 2))
>     (funcall fun1 x x)
>     (funcall fun2 x x)))
> 
> Form 2:
> 
> (defun one-or-another (fun1 fun2 x)
>   (funcall 
>    (if (zerop (mod (get-internal-real-time) 2))
>      fun1 fun2)
>      x x))
> 
> (one-or-another #'* #'+ 4)
> => sometimes 8, sometimes 16

I would use Form 1 if the parameters were as simple as this example.  
But if the expressions in the parameter were complex I would use Form 2 
(actually, the variant that others have posted where a local variable is 
bound to the selected function), so that the parallel structure would be 
obvious.

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
From: Kenny Tilton
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <tVVcd.82628$Ot3.69216@twister.nyc.rr.com>
Michiel Borkent wrote:

> Form 1:
> 
> (defun one-or-another (fun1 fun2 x)
>   (if (zerop (mod (get-internal-real-time) 2))
>     (funcall fun1 x x)
>     (funcall fun2 x x)))
> 
> Form 2:
> 
> (defun one-or-another (fun1 fun2 x)
>   (funcall 
>    (if (zerop (mod (get-internal-real-time) 2))
>      fun1 fun2)
>      x x))

The latter, because it emphasizes that only the function called is 
affected by the time.

kt

-- 
Cells? Cello? Celtik?: http://www.common-lisp.net/project/cells/
Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film
From: Vassil Nikolov
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <lz4qkr70bu.fsf@janus.vassil.nikolov.names>
··············@gmail.com (Michiel Borkent) writes:

> Form 1:
>
> (defun one-or-another (fun1 fun2 x)
>   (if (zerop (mod (get-internal-real-time) 2))
>     (funcall fun1 x x)
>     (funcall fun2 x x)))
>
> Form 2:
>
> (defun one-or-another (fun1 fun2 x)
>   (funcall 
>    (if (zerop (mod (get-internal-real-time) 2))
>      fun1 fun2)
>      x x))

  Depends on the "lexical size" of the expressions involved, e.g.

    (if (a-large-and-complicated-expression)
        (funcall f1 x y)  ;arguments are just variables,
      (funcall f2 x y))   ; preferably with short names

  but

    (funcall (if (an-expression) f1 f2)
             (some-long-and-complicated)
             (argument-list))

  and still, I'd tend to prefer (FUNCALL (IF ...) ...) if I want to be
  sure that the argument list is the same for either function (and if
  I am sure I want that).

  ---Vassil.

-- 
Vassil Nikolov <········@poboxes.com>

Hollerith's Law of Docstrings: Everything can be summarized in 72 bytes.
From: Mario S. Mommer
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <fzr7nvjkfb.fsf@germany.igpm.rwth-aachen.de>
I don't really give a damn either way. Which one I use will probably
depend on which one comes to my mind first.

What I'm really curious about is - why do people bother having a
preference for any one? I mean, why does it matter at all? Both work,
both are correct, both can be understood, etc. so...

··············@gmail.com (Michiel Borkent) writes:
> Form 1:
>
> (defun one-or-another (fun1 fun2 x)
>   (if (zerop (mod (get-internal-real-time) 2))
>     (funcall fun1 x x)
>     (funcall fun2 x x)))
>
> Form 2:
>
> (defun one-or-another (fun1 fun2 x)
>   (funcall 
>    (if (zerop (mod (get-internal-real-time) 2))
>      fun1 fun2)
>      x x))
>
> (one-or-another #'* #'+ 4)
> => sometimes 8, sometimes 16
>
> Grtz,
> Michiel
From: Barry Margolin
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <barmar-52BD95.02484719102004@comcast.dca.giganews.com>
In article <··············@germany.igpm.rwth-aachen.de>,
 Mario S. Mommer <········@yahoo.com> wrote:

> What I'm really curious about is - why do people bother having a
> preference for any one? I mean, why does it matter at all? Both work,
> both are correct, both can be understood, etc. so...

Because readability of code is important.  And if you conform to popular 
idioms, people will find your code more readable.

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
From: Mario S. Mommer
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <fzd5zfyras.fsf@germany.igpm.rwth-aachen.de>
Barry Margolin <······@alum.mit.edu> writes:
> In article <··············@germany.igpm.rwth-aachen.de>,
>  Mario S. Mommer <········@yahoo.com> wrote:
>
>> What I'm really curious about is - why do people bother having a
>> preference for any one? I mean, why does it matter at all? Both work,
>> both are correct, both can be understood, etc. so...
>
> Because readability of code is important. And if you conform to
> popular idioms, people will find your code more readable.

Yeah, but AFAICT, Both are readable, and both are common idioms.
From: Barry Margolin
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <barmar-059689.08474419102004@comcast.dca.giganews.com>
In article <··············@germany.igpm.rwth-aachen.de>,
 Mario S. Mommer <········@yahoo.com> wrote:

> Barry Margolin <······@alum.mit.edu> writes:
> > In article <··············@germany.igpm.rwth-aachen.de>,
> >  Mario S. Mommer <········@yahoo.com> wrote:
> >
> >> What I'm really curious about is - why do people bother having a
> >> preference for any one? I mean, why does it matter at all? Both work,
> >> both are correct, both can be understood, etc. so...
> >
> > Because readability of code is important. And if you conform to
> > popular idioms, people will find your code more readable.
> 
> Yeah, but AFAICT, Both are readable, and both are common idioms.

If the parameter expressions were several lines long, do you still think 
that both would be as readable?

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
From: Mario S. Mommer
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <fzr7nuybbr.fsf@germany.igpm.rwth-aachen.de>
Barry Margolin <······@alum.mit.edu> writes:
>  Mario S. Mommer <········@yahoo.com> wrote:
>> 
>> Yeah, but AFAICT, Both are readable, and both are common idioms.
>
> If the parameter expressions were several lines long, do you still think 
> that both would be as readable?

Actually, yes.
From: Michiel Borkent
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <a58e8f47.0410190616.56662e47@posting.google.com>
> What I'm really curious about is - why do people bother having a
> preference for any one? I mean, why does it matter at all? Both work,
> both are correct, both can be understood, etc. so...

Because I am trying to find out what people find esthetical
programming. To put it in extreme words,  for me the second form gives
me the feeling I am working in an elegant and flexibel language, while
the first form gives me the feeling I was bound to a language that is
narrowing my thoughts and forces me to type kind of the same things
over and over again, while I don't want to. When I collect the
thoughts and arguments of other subjects, it might trigger some
interesting thoughts in my mind which I can write down in a report I
am working on in which one chapter is going to be about esthetics of
Lisp vs. other Languages.

Greetings,
Michiel
From: Mario S. Mommer
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <fzmzyiyay1.fsf@germany.igpm.rwth-aachen.de>
··············@gmail.com (Michiel Borkent) writes:
> Because I am trying to find out what people find esthetical
> programming. To put it in extreme words,  for me the second form gives
> me the feeling I am working in an elegant and flexibel language, while
> the first form gives me the feeling I was bound to a language that is
> narrowing my thoughts and forces me to type kind of the same things
> over and over again, while I don't want to.

well...

> When I collect the thoughts and arguments of other subjects, it
> might trigger some interesting thoughts in my mind which I can write
> down in a report I am working on in which one chapter is going to be
> about esthetics of Lisp vs. other Languages.

...what I find beautiful in Lisp is that you can use any of those
forms. The absence of a good-practice reign of terror is really a very
nice feature.
From: Douglas Philips
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <417544c2_1@news.nauticom.net>
On 2004-10-19 02:23:20 -0400, Mario S. Mommer <········@yahoo.com> said:
> What I'm really curious about is - why do people bother having a
> preference for any one? I mean, why does it matter at all? Both work,
> both are correct, both can be understood, etc. so..

So far (as the news flows), I haven't seen anyone argue this on correctness.
If both parameter lists are supposed to be the same, then having them 
duplicated can only be bad.

Sure, in trivial cases, the parallelism will be obvious. If you have 
several lines of parameter list (as some have suggested the criteria 
should be), then perhaps you need to clarify the code so that the 
function selection and parameter aggregation (for lack of a better 
word) do not mutually interfere with each other.

If it is one parameter list, it should be one parameter.
That you can "get away with it" is a convenience argument. Personally 
(since you did ask), I've been bitten by far too many convenience bugs. 
If clear code is a goal or a discipline or even a consideration, then 
this should be a no brainer, n'est-ce pas?

<D\'gou
From: Kenny Tilton
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <SMcdd.31253$4C.6423392@twister.nyc.rr.com>
Mario S. Mommer wrote:
> I don't really give a damn either way. Which one I use will probably
> depend on which one comes to my mind first.
> 
> What I'm really curious about is - why do people bother having a
> preference for any one? I mean, why does it matter at all? Both work,
> both are correct, both can be understood, etc. so...

Quality. Craftmanship. Code Hell is reached thru many small deviations 
from The Way. Always move towards the light. All running code "works", 
but most running code is impossible to maintain and a lot of it contains 
bugs whose combinatorial number simply has not come up. Some of us 
believe that things like third normal form in relational design make 
sense for code, too. One does not store data redundantly, and one does 
not code redundantly. Someday that argument list will change and the 
programmer will have a sneezing fit after changing one but before 
changing the other and never get back to it. If the second branch is a 
rare one, the first time it will run is when it has to land a 747. 
Craftsman know there may be nine ways to skin a cat, but there is 
exactly one best way to skin that cat.* What happens when the code gets 
refactored such that the function to be called gets decided outside the 
function which calls it? Consider the quality of the different edits 
(not the quantity) argues further against redundancy. Billions of games 
of chess can be played from any given middle game position, but good 
chess players know there is One Best Move to be found. Something like that.

btw, elsewhere I saw aesthetics and elegance mentioned. No, this is 
about correctness, not at the instructional, computational level, but at 
  the level of human engineering. ie, Correctness includes consideration 
of stressed-out humans of uneven ability reading, maintaining, 
debugging, and refactoring code.

kenny

* No animals were harmed in this analogy.


> 
> ··············@gmail.com (Michiel Borkent) writes:
> 
>>Form 1:
>>
>>(defun one-or-another (fun1 fun2 x)
>>  (if (zerop (mod (get-internal-real-time) 2))
>>    (funcall fun1 x x)
>>    (funcall fun2 x x)))
>>
>>Form 2:
>>
>>(defun one-or-another (fun1 fun2 x)
>>  (funcall 
>>   (if (zerop (mod (get-internal-real-time) 2))
>>     fun1 fun2)
>>     x x))
>>
>>(one-or-another #'* #'+ 4)
>>=> sometimes 8, sometimes 16
>>
>>Grtz,
>>Michiel

-- 
Cells? Cello? Celtik?: http://www.common-lisp.net/project/cells/
Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film
From: Duane Rettig
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <43c0aef40.fsf@franz.com>
Kenny Tilton <·······@nyc.rr.com> writes:

> * No animals were harmed in this analogy.

Then how do you know the premise is true?

:-)

-- 
Duane Rettig    ·····@franz.com    Franz Inc.  http://www.franz.com/
555 12th St., Suite 1450               http://www.555citycenter.com/
Oakland, Ca. 94607        Phone: (510) 452-2000; Fax: (510) 452-0182   
From: Kenny Tilton
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <Igfdd.31259$4C.6438720@twister.nyc.rr.com>
Duane Rettig wrote:

> Kenny Tilton <·······@nyc.rr.com> writes:
> 
> 
>>* No animals were harmed in this analogy.
> 
> 
> Then how do you know the premise is true?
> 
> :-)
> 

Omigod. Duane, the cat is supposed to be dead before you skin it.*

kenny

* Reminding me that pitcher John Smoltz of the Atlanta Braves once had 
to be treated by the team trainer for a burn on his chest. He got the 
burn while ironing a shirt. A shirt he was wearing. k

-- 
Cells? Cello? Celtik?: http://www.common-lisp.net/project/cells/
Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film
From: Rahul Jain
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <87zn2itnor.fsf@nyct.net>
Kenny Tilton <·······@nyc.rr.com> writes:

> Omigod. Duane, the cat is supposed to be dead before you skin it.*

What if it's both dead and alive at the same time?

-- 
Rahul Jain
·····@nyct.net
Professional Software Developer, Amateur Quantum Mechanicist
From: Cesar Rabak
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <4175BBA4.1080604@acm.org>
Rahul Jain escreveu:
> Kenny Tilton <·······@nyc.rr.com> writes:
> 
> 
>>Omigod. Duane, the cat is supposed to be dead before you skin it.*
> 
> 
> What if it's both dead and alive at the same time?
> 
The 'Amateur Quantum Mechanicist' half manifesting?

LOL
From: Rahul Jain
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <87acuit1xu.fsf@nyct.net>
Cesar Rabak <······@acm.org> writes:

> Rahul Jain escreveu:
>> Kenny Tilton <·······@nyc.rr.com> writes:
>>
>>>Omigod. Duane, the cat is supposed to be dead before you skin it.*
>> What if it's both dead and alive at the same time?
>>
> The 'Amateur Quantum Mechanicist' half manifesting?

I suppose if I expounded on my theory as to why a cat can't be dead and
alive at the same time, that would be totally manifesting it. ;)

-- 
Rahul Jain
·····@nyct.net
Professional Software Developer, Amateur Quantum Mechanicist
From: Svein Ove Aas
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <cl5ap0$qkv$1@services.kq.no>
Rahul Jain wrote:

> Cesar Rabak <······@acm.org> writes:
> 
>> Rahul Jain escreveu:
>>> Kenny Tilton <·······@nyc.rr.com> writes:
>>>
>>>>Omigod. Duane, the cat is supposed to be dead before you skin it.*
>>> What if it's both dead and alive at the same time?
>>>
>> The 'Amateur Quantum Mechanicist' half manifesting?
> 
> I suppose if I expounded on my theory as to why a cat can't be dead and
> alive at the same time, that would be totally manifesting it. ;)
> 
Besides, you'd be wrong.


...did it work?
 
From: Rahul Jain
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <87y8i0lpdl.fsf@nyct.net>
Svein Ove Aas <·········@aas.no> writes:

> Rahul Jain wrote:
>
>> I suppose if I expounded on my theory as to why a cat can't be dead and
>> alive at the same time, that would be totally manifesting it. ;)
>> 
> Besides, you'd be wrong.
>
>
> ...did it work?

Did what work? You flamebaitbaiting me into calling you a fool for
ignoring the fact that no one has ever directly observed a
superposition? Maybe... maybe not. ;)

-- 
Rahul Jain
·····@nyct.net
Professional Software Developer, Amateur Quantum Mechanicist
From: Svein Ove Aas
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <cl7lur$gfs$2@services.kq.no>
Rahul Jain wrote:

> Svein Ove Aas <·········@aas.no> writes:
> 
>> Rahul Jain wrote:
>>
>>> I suppose if I expounded on my theory as to why a cat can't be dead and
>>> alive at the same time, that would be totally manifesting it. ;)
>>> 
>> Besides, you'd be wrong.
>>
>>
>> ...did it work?
> 
> Did what work? You flamebaitbaiting me into calling you a fool for
> ignoring the fact that no one has ever directly observed a
> superposition? Maybe... maybe not. ;)
> 
No, I was hoping you'd go ahead and expound on your theory anyway.
Baiting, yes. Flamebaiting... nope, I don't think so.

Where do you usually hang out to discuss such things? 
From: Rahul Jain
Subject: Re: Which form do you prefer (and why)?
Date: 
Message-ID: <87r7nnd19n.fsf@nyct.net>
Svein Ove Aas <·········@aas.no> writes:

> No, I was hoping you'd go ahead and expound on your theory anyway.
> Baiting, yes. Flamebaiting... nope, I don't think so.

Oh... well it has to do with decoherence with key insight provided by a
paper describing an experiment where hot fullerenes were observed to
spontaneously decohere with the same probability as they were expected
to radiate a photon of the appropriate wavelength to determine which
slit of an interferometer the fullerene passed through.

> Where do you usually hang out to discuss such things?

sci.physics.research is where I talk about these kinds of things, but I
haven't yet presented this idea directly. I have, however, interjected
musings along this path in the middle of related discussions, to little
effect.

-- 
Rahul Jain
·····@nyct.net
Professional Software Developer, Amateur Quantum Mechanicist