From: Ken Tilton
Subject: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <47ae04d2$0$25039$607ed4bc@cv.net>
I literally grabbed a the first function I saw in my code for an experiment:

; --- the doc ---
; (I just moved the doc down below so one can encounter the code
; the normal way we encounter OPC, cold.)
;
; --- assuming like most yobs you haven't even looked at Arc ---
; CL: (mapcar (lambda (x) (mod x 42)) y)
; Arc: (map [mod _ 42] y) or (map (fn (x) (mod x 42)) y)

I'll show the Arc version first cuz I think it is more obscure and I 
want you to see it before the CL "dummies" version(s) makes it obvious 
what is going on:

; --- Arc version -----------
;
(def tf-traverse-results (tf result-fn)
   (when tf
     (tf-traverse tf
       [map [map result-fn (results _)]
             (derivations _)]]))

; --- CL version --------------

(defun tf-traverse-results (tf fn)
   (when tf
     (tf-traverse tf
       (lambda (tf)
         (loop for d in (derivations tf) do
               (loop for result in (results d)
                   do (funcall fn result)))))))

The fun thing there is that I am cheating by using LOOP, which shares 
with Arc a goal of achieving brevity and fewer parens at the cost of 
learning syntax, but ...OK, without loop (but using dolist instead!):

(defun tf-traverse-results (tf fn)
   (when tf
     (tf-traverse tf
       (lambda (tfsub)
         (dolist (d (derivations tfsub))
           (dolist (result (results d))
             (funcall fn result)))))))

[Note to self: maybe don't use LOOP for everything?]

Turns out it is an interesting example because in Arc we get nested _s, 
fortunately not needing access to the outer binding of _ once the inner 
is bound (so it ain't all /that/ nested).

Of course one could always use fn:

; --- Arc2 ---
(def tf-traverse-results (tf result-fn)
   (when tf
     (tf-traverse tf
       (fn (tf)
         (map (fn (d)
                (map result-fn (results d)))
           (derivations tf))))))

Keeping one of the abbreviated fns:

; --- Arc3 ---

(def tf-traverse-results (tf result-fn)
   (when tf
     (tf-traverse tf
       (fn (tf)
         (map [map result-fn (results _)]
           (derivations tf))))))

It was a random choice, but the tight packing of all these iterations 
and 1st-class functions might be confusing the issue. Anyway...

The CL versions are both trivial to read and even make obvious the 
organization of the data structures if one did not know them, which 
could be me because who can remember all that in a huge application?

I am not sure on the Arc version since I am still new to reading it, but 
it seems like it would always take more work to unwind in my head. As 
for the brevity of the denser version, hey, why did God create scroll bars?

kenny

The doc:
; A transformation (tf) consists in part of 1 or more derivations
; A derivation relates 1+ operands to 1+ result expressions
; A transformation can have child transformations, forming a TF tree
; tf-traverse visits every TF in a TF tree applying a function
; tf-traverse-results applies a function to each result in each
;   derivation of each TF in a tree

-- 
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius

From: danb
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <f97f1500-ed60-4f51-bced-b531e228f13d@f10g2000hsf.googlegroups.com>
On Feb 9, 1:53 pm, Ken Tilton <···········@optonline.net> wrote:
>            [map [map result-fn (results _)] (derivations _)]]
(lambda (tf)
  (mapcar result-fn (nconc #'results (mapcar #'derivations tf))))

(not tested)

--Dan
www.prairienet.org/~dsb/
From: danb
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <c3a718e0-a348-40bc-9d49-6f0d89321e67@s37g2000prg.googlegroups.com>
> On Feb 9, 1:53 pm, Ken Tilton <···········@optonline.net> wrote:
>            [map [map result-fn (results _)] (derivations _)]]

Oops, just a couple changes, plus mapc per John's post:
(lambda (tf)
  (mapc result-fn (nconc (mapcar #'results (derivations tf)))))

(still not tested)

--Dan
www.prairienet.org/~dsb/
From: danb
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <fcf4d042-7e62-4e16-8408-f2ab2503f65b@p69g2000hsa.googlegroups.com>
> On Feb 9, 1:53 pm, Ken Tilton <···········@optonline.net> wrote:
>            [map [map result-fn (results _)] (derivations _)]]

(lambda (tf) (mapc result-fn (mapcan #'results (derivations tf))))

(last try)

--Dan
www.prairienet.org/~dsb/
From: Ken Tilton
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info  inside)
Date: 
Message-ID: <47ae567a$0$7890$607ed4bc@cv.net>
danb wrote:
 > On Feb 9, 1:53 pm, Ken Tilton <···········@optonline.net> wrote:
 >
 >>           [map [map result-fn (results _)] (derivations _)]]
 >
 > (lambda (tf)
 >   (mapcar result-fn (nconc #'results (mapcar #'derivations tf))))
 >

Why you consing whore, you!

John Thingstad wrote:
 > (defun tf-traverse-results (tf result-fn)
 >   (labels ((on-results (d)
 >              (mapc (lambda (r) (funcall result-fn  r)) (results d)))
 >            (on-derivations (tf)
 >              (mapc #'on-results (derivations tf))))
 >     (when tf (tf-traverse tf (on-derivations tf)))))

Oh, fuck, I've had a stroke, I see not one but two labels on the screen 
for this trivial nested iteration. Someone quick call 911 for me!

danb wrote:
 > Oops, just a couple changes, plus mapc per John's post:
 > (lambda (tf)
 >   (mapc result-fn (nconc (mapcar #'results (derivations tf)))))

We now have two top Lisp consultants collaborating on this tour de force 
demonstration of the Unbearable Powerfulness of Lisp?

Youse guys are scaring me.

danb wrote:
> (lambda (tf) (mapc result-fn (mapcan #'results (derivations tf))))
> 
> (last try)

Oh, admit it, you have been thru two more versions already and started a 
commom-lisp.net project for it.

John Thingstad wrote:
 > Could it be that you are not used to a functional programming style
 > using  the map family?

Could it be that you are not used to walking upright?

<sigh>

kenny


-- 
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius
From: Leandro Rios
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <47ae1487$0$1347$834e42db@reader.greatnowhere.com>
Ken Tilton escribi�:

Sorry, but I won't read this message then. I prefer to leave my dead 
where they are. :)

Leandro

PS: Lapsus typeae?
From: Ken Tilton
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <47ae50fa$0$7869$607ed4bc@cv.net>
Leandro Rios wrote:
> Ken Tilton escribi�:
> 
> Sorry, but I won't read this message then. I prefer to leave my dead 
> where they are. :)

PWWUAAAAAHHAHAA talkabout a freudian PWUUAHAHAHHAHAHAA....

> PS: Lapsus typeae?

Oh I think we can do better than that... the first thing I do in these 
cases is meditate on my keyboard. Is the D near the H? Not near enough: 
Kenny's Unconscious has spoken! No clue what he meant, you'd have to ask 
him somewhere towards the end of the next Lisp-NYC meeting, but before 
he decides to take on the bouncers.

hth, kenny

-- 
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius
From: ···········@gmail.com
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <952ac558-db94-4aad-a924-7da33c1bdbc8@p69g2000hsa.googlegroups.com>
> (defun tf-traverse-results (tf fn)
>    (when tf
>      (tf-traverse tf
>        (lambda (tfsub)
>          (dolist (d (derivations tfsub))
>            (dolist (result (results d))
>              (funcall fn result)))))))


> The CL versions are both trivial to read and even make obvious the
> organization of the data structures if one did not know them, which
> could be me because who can remember all that in a huge application?
>
> I am not sure on the Arc version since I am still new to reading it, but
> it seems like it would always take more work to unwind in my head. As
> for the brevity of the denser version, hey, why did God create scroll bars?

I find that the readability of a programming language often has a lot
to do with the style of the programmer. Perl doesn't HAVE to look like
nonsense. Arc can easily look just as readable as the CL with the
'dolist' macro calls by using Arc's 'each' macro (I'm pretty sure it's
called each, I unfortunately cannot double check at this time). They
are basically the same thing.

Of course, though, if a programmer was determined enough, they can
make Arc almost impossible to read by writing code as merely a slew of
nested functions, all using square brackets. But then again, a
determined programmer can make any code incomprehensible regardless of
what language they are using. The important thing is to make sure you
don't take so many shortcuts that your code becomes illegible.
From: Ken Tilton
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info  inside)
Date: 
Message-ID: <47aea538$0$15176$607ed4bc@cv.net>
···········@gmail.com wrote:
>>(defun tf-traverse-results (tf fn)
>>   (when tf
>>     (tf-traverse tf
>>       (lambda (tfsub)
>>         (dolist (d (derivations tfsub))
>>           (dolist (result (results d))
>>             (funcall fn result)))))))
> 
> 
> 
>>The CL versions are both trivial to read and even make obvious the
>>organization of the data structures if one did not know them, which
>>could be me because who can remember all that in a huge application?
>>
>>I am not sure on the Arc version since I am still new to reading it, but
>>it seems like it would always take more work to unwind in my head. As
>>for the brevity of the denser version, hey, why did God create scroll bars?
> 
> 
> I find that the readability of a programming language often has a lot
> to do with the style of the programmer.

Yep.

> Perl doesn't HAVE to look like
> nonsense. Arc can easily look just as readable as the CL with the
> 'dolist' macro calls by using Arc's 'each' macro (I'm pretty sure it's
> called each, I unfortunately cannot double check at this time). They
> are basically the same thing.

Oh, cripes, I came this close to asking for improvements on the Arc 
code, I already have forgotten a lot of Arc. Thx:

(def tf-traverse-results (tf fn)
   (when tf
     (tf-traverse tf
       [each d (derivations _)
         (each result (results d)
           (fn result))])))

What do you think of that whole _ thing? That strikes me as a net loss 
cuz I lost the mnemonic reminder in return for saving not too many 
characters:

(def tf-traverse-results (tf fn)
   (when tf
     (tf-traverse tf
       (fn (tf)
         (each d (derivations tf)
           (each result (results d)
             (fn result))])))

I should ... oh, cripes, at some point I did enhance tf-traverse to 
handle nil sensibly, everybody gets a little shorter:

(def tf-traverse-results (tf fn)
   (tf-traverse tf
     [each d (derivations _)
         (each result (results d)
           (fn result))])))

(defun tf-traverse-results (tf fn)
   (tf-traverse tf
     (lambda (tf)
       (dolist (d (derivations tf))
         (dolist (result (results d))
           (funcall fn result))))))

Modest edge for Arc, to my eyes. Not a good comparison after all? Unless 
it turns out that so much code turns out not to benefit from Arc's 
economies that nothing has been accomplished.

The funny thing is that Graham does not like loop, which is great at 
making code more succinct and less parenthetical.

kenny



-- 
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius
From: Rob Warnock
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info  inside)
Date: 
Message-ID: <_aSdneU8Gt3rRjPanZ2dnUVZ_v6rnZ2d@speakeasy.net>
Ken Tilton  <·········@gmail.com> wrote:
+---------------
| What do you think of that whole _ thing?
+---------------

I think it doesn't scale. ;-}  I muchly prefer my own #$ readmacro
[or one of the many similar variants discussed here last December]:

    > (mapcar #$(+ (* 100 $2) $1) '(1 2 3 4) '(5 6 7 8) '(9 10 11 12))

    (501 602 703 804)
    > 

An unintended [but nice] consequence of the implementation
[it just uses READ to pick up the LAMBDA body] was that it
can also be used as an abbreviation for CONSTANTLY:

    > (mapcar #$57 (iota 10))

    (57 57 57 57 57 57 57 57 57 57)
    > 


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: jayessay
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <m37ihb8i9m.fsf@sirius.goldenthreadtech.com>
····@rpw3.org (Rob Warnock) writes:

> Ken Tilton  <·········@gmail.com> wrote:
> +---------------
> | What do you think of that whole _ thing?
> +---------------
> 
> I think it doesn't scale. ;-}  I muchly prefer my own #$ readmacro
> [or one of the many similar variants discussed here last December]:
> 
>     > (mapcar #$(+ (* 100 $2) $1) '(1 2 3 4) '(5 6 7 8) '(9 10 11 12))
> 
>     (501 602 703 804)

What happens with the last list here?  I would:

(all (+ (* 100 y) x) :suchthat (:|| (x :in '(1 2 3 4)) (y :in '(5 6 7 8))))

(501 602 703 804)

Or better formatted:

(all (+ (* 100 y) x) :suchthat
     (:|| (x :in '(1 2 3 4))
          (y :in '(5 6 7 8))))


>     > (mapcar #$57 (iota 10))
> 
>     (57 57 57 57 57 57 57 57 57 57)
>     > 

(all 57 :suchthat (i :in (the-range 1 10)))

(57 57 57 57 57 57 57 57 57 57)

Hmmm, never tried that before.  At first I wasn't sure if this was a
"feature" or a "bug", but I think it does make sense.


Here's a somewhat goofier (contrived) one:

(all (x y (:x+y= (+ x y)
           :x*y= (* x y)
           (:x x :y y :x^y=(expt x y))))
     :suchthat
       (evenp x)
       (x :in (the-range 1 100))
       (y :in (the-range 1 100)))

((2 1 (:x+y= 3 :x*y= 2 (:x 2 :y 1 :x^y= 2)))
 (2 2 (:x+y= 4 :x*y= 4 (:x 2 :y 2 :x^y= 4)))
 (2 3 (:x+y= 5 :x*y= 6 (:x 2 :y 3 :x^y= 8)))
 (2 4 (:x+y= 6 :x*y= 8 (:x 2 :y 4 :x^y= 16)))
 (2 5 (:x+y= 7 :x*y= 10 (:x 2 :y 5 :x^y= 32)))
 (2 6 (:x+y= 8 :x*y= 12 (:x 2 :y 6 :x^y= 64)))
 (2 7 (:x+y= 9 :x*y= 14 (:x 2 :y 7 :x^y= 128)))
 (2 8 (:x+y= 10 :x*y= 16 (:x 2 :y 8 :x^y= 256)))
 (2 9 (:x+y= 11 :x*y= 18 (:x 2 :y 9 :x^y= 512)))
 (2 10 (:x+y= 12 :x*y= 20 (:x 2 :y 10 :x^y= 1024))) ...)


Or slightly different (two sets returned):

(all (x y) (:x+y= (+ x y)
            :x*y= (* x y)
            (:x x :y y :x^y=(expt x y)))
     :suchthat
       (evenp x)
       (x :in (the-range 1 100))
       (y :in (the-range 1 100)))

((2 1) (2 2) (2 3) (2 4) (2 5) (2 6) (2 7) (2 8) (2 9) (2 10) ...)
((:x+y= 3 :x*y= 2 (:x 2 :y 1 :x^y= 2))
 (:x+y= 4 :x*y= 4 (:x 2 :y 2 :x^y= 4))
 (:x+y= 5 :x*y= 6 (:x 2 :y 3 :x^y= 8))
 (:x+y= 6 :x*y= 8 (:x 2 :y 4 :x^y= 16))
 (:x+y= 7 :x*y= 10 (:x 2 :y 5 :x^y= 32))
 (:x+y= 8 :x*y= 12 (:x 2 :y 6 :x^y= 64))
 (:x+y= 9 :x*y= 14 (:x 2 :y 7 :x^y= 128))
 (:x+y= 10 :x*y= 16 (:x 2 :y 8 :x^y= 256))
 (:x+y= 11 :x*y= 18 (:x 2 :y 9 :x^y= 512))
 (:x+y= 12 :x*y= 20 (:x 2 :y 10 :x^y= 1024)) ...)



/Jon

-- 
'j' - a n t h o n y at romeo/charley/november com
From: Rob Warnock
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <_q6dndKLnPRhDSzanZ2dnUVZ_vOlnZ2d@speakeasy.net>
jayessay  <······@foo.com> wrote:
+---------------
| ····@rpw3.org (Rob Warnock) writes:
| > I muchly prefer my own #$ readmacro
| > [or one of the many similar variants discussed here last December]:
| >     > (mapcar #$(+ (* 100 $2) $1) '(1 2 3 4) '(5 6 7 8) '(9 10 11 12))
| >     (501 602 703 804)
| 
| What happens with the last list here?
+---------------

It's ignored. Or, rather, it's bound to $3, but $3 is ignored! ;-}  ;-}

Here's the definition of my current simpleminded version of #$:

    (defun set-sharp-dollar-reader ()
      (flet ((sharp-dollar-reader (s c p)
	       (declare (ignore c p))
	       (let* ((form (read s t nil t)))
		 `(lambda (&optional $1 $2 $3 $4 $5 $6 $7 $8 $9 &rest $*)
		    (declare (ignorable $1 $2 $3 $4 $5 $6 $7 $8 $9 $*))
		    ,@(if (and (consp form) (consp (car form)))
			form
			(list form))))))
	(set-dispatch-macro-character #\# #\$ #'sharp-dollar-reader)))

Now in the thread last December, it was suggested that it might be
better to walk the FORM for variables of the form "${integer}" and
only declare arguments from $1 up to the highest seen [and then add
the &REST $* after that]. Yeah, that would be better, but I haven't
done it yet. Not enough round tuits...  ;-}


-Rob

p.s. The reason for the IF inside the LAMBDA may be non-obvious; it's
just a convenience hack to provide an implicit PROGN sometimes, e.g.:

    > (mapcar #$((format t "Thrice ~a...~%" $1) (* $1 3)) (iota 5))
    Thrice 0...
    Thrice 1...
    Thrice 2...
    Thrice 3...
    Thrice 4...
    (0 3 6 9 12)
    > 

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Leslie P. Polzer
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <bc785cc0-15ec-4f05-810d-4496616de00f@d21g2000prf.googlegroups.com>
On Feb 11, 7:23 pm, jayessay <······@foo.com> wrote:
> ····@rpw3.org (Rob Warnock) writes:
> > I think it doesn't scale. ;-}  I muchly prefer my own #$ readmacro
> > [or one of the many similar variants discussed here last December]:

Where's the thread on this?
From: Rob Warnock
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <g6qdnZ-lEeCNHyjanZ2dnUVZ_gqdnZ2d@speakeasy.net>
Leslie P. Polzer <·············@gmx.net> wrote:
+---------------
| ····@rpw3.org (Rob Warnock) writes:
| > I think it doesn't scale. ;-}  I muchly prefer my own #$ readmacro
| > [or one of the many similar variants discussed here last December]:
| 
| Where's the thread on this?
+---------------

Try starting at <·····································@speakeasy.net>
and working backwards/forwards from there. That one was
"Subject: Re: mapcar using a function with one argument fixed",
but the "Subject:" may have mutated during the thread.


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: John Thingstad
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <op.t6a0s1rkut4oq5@pandora.alfanett.no>
P� Sun, 10 Feb 2008 08:18:12 +0100, skrev Ken Tilton  
<···········@optonline.net>:

>
> I should ... oh, cripes, at some point I did enhance tf-traverse to  
> handle nil sensibly, everybody gets a little shorter:
>
> (def tf-traverse-results (tf fn)
>    (tf-traverse tf
>      [each d (derivations _)
>          (each result (results d)
>            (fn result))])))
>

Interestingly..

> (each c "Hello" (prn c))
H
e
l
l
o
nil

> (each c '(H e l l o) (prn c))
H
e
l
l
o
nil

Also handles table (CL hashtable)

Lookes like this:

(mac each (var expr . body)
   (w/uniq (gseq g)
     `(let ,gseq ,expr
        (if (alist ,gseq)
             ((afn (,g)
                (when (acons ,g)
                  (let ,var (car ,g) ,@body)
                  (self (cdr ,g))))
              ,gseq)
            (isa ,gseq 'table)
             (maptable (fn (,g ,var) ,@body)
                       ,gseq)
             (for ,g 0 (- (len ,gseq) 1)
               (let ,var (,gseq ,g) ,@body))))))

The first case starts at (alist..
Tail recursive call to cdr for iteration
afn is a anonymous function that can refer to itself with self

(isa .. 'table) starts the next case
and uses maptable

Third case starts at (for..
It took me a couple of minutes to see this as it appears to belong to (isa  
... 'table)
Also note ("Hello" 3) => #\l

--------------
John Thingstad
From: jayessay
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <m33arz8hgn.fsf@sirius.goldenthreadtech.com>
"John Thingstad" <·······@online.no> writes:

> På Sun, 10 Feb 2008 08:18:12 +0100, skrev Ken Tilton
> <···········@optonline.net>:
> 
> >
> > I should ... oh, cripes, at some point I did enhance tf-traverse to
> > handle nil sensibly, everybody gets a little shorter:
> >
> > (def tf-traverse-results (tf fn)
> >    (tf-traverse tf
> >      [each d (derivations _)
> >          (each result (results d)
> >            (fn result))])))
> >
> 
> Interestingly..
> 
> > (each c "Hello" (prn c))
> H
> e
> l
> l
> o
> nil

Seems reasonable to me.  Seems exactly what you would want/expect.


> > (each c '(H e l l o) (prn c))
> H
> e
> l
> l
> o
> nil
> 
> Also handles table (CL hashtable)


(let ((tbl (make-hash-table)))
  (dolist (x '(:hash-one :hash-two :hash-three))
    (setf (gethash x tbl) x))
  (all w x y z :suchthat
       (:|| (w :in "abc")
            (x :in #(1 2 3))
            (y :in '(one two three))
            (z :in tbl))))

(#\a #\b #\c)
(1 2 3)
(ariadne.agents::one ariadne.agents::two ariadne.agents::three)
(:hash-two :hash-one :hash-three)

Also works with any other kind of set (representation).  Compilation
and runtime extensible for domain specific set reps.


/Jon

-- 
'j' - a n t h o n y at romeo/charley/november com
From: Rich Hickey
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <222e9a77-d81c-408f-bf34-23b9805678eb@v67g2000hse.googlegroups.com>
On Feb 10, 2:18 am, Ken Tilton <···········@optonline.net> wrote:

> I should ... oh, cripes, at some point I did enhance tf-traverse to
> handle nil sensibly, everybody gets a little shorter:
>
> (def tf-traverse-results (tf fn)
>    (tf-traverse tf
>      [each d (derivations _)
>          (each result (results d)
>            (fn result))])))
>
> (defun tf-traverse-results (tf fn)
>    (tf-traverse tf
>      (lambda (tf)
>        (dolist (d (derivations tf))
>          (dolist (result (results d))
>            (funcall fn result))))))
>
> Modest edge for Arc, to my eyes. Not a good comparison after all? Unless
> it turns out that so much code turns out not to benefit from Arc's
> economies that nothing has been accomplished.
>

3 versions in Clojure for comparison:

;for is lazy list comprehension
;scan is needed because you are calling f for side-effects

(defn tf-traverse-results [tf f]
  (tf-traverse tf
    (fn [tf]
      (scan (for [d (derivations tf) result (results d)] (f
result))))))

;doseq might make side-effects more obvious

(defn tf-traverse-results [tf f]
  (tf-traverse tf
    (fn [tf]
      (doseq r (for [d (derivations tf) result (results d)] result)
	 (f r)))))

;akin to CL version:

(defn tf-traverse-results [tf f]
  (tf-traverse tf
    (fn [tf]
       (doseq d (derivations tf)
	 (doseq result (results d)
           (f result))))))

Rich
From: Rainer Joswig
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <joswig-2D3194.23392510022008@news-europe.giganews.com>
In article 
<····································@v67g2000hse.googlegroups.com>,
 Rich Hickey <··········@gmail.com> wrote:

> On Feb 10, 2:18 am, Ken Tilton <···········@optonline.net> wrote:
> 
> > I should ... oh, cripes, at some point I did enhance tf-traverse to
> > handle nil sensibly, everybody gets a little shorter:
> >
> > (def tf-traverse-results (tf fn)
> >    (tf-traverse tf
> >      [each d (derivations _)
> >          (each result (results d)
> >            (fn result))])))
> >
> > (defun tf-traverse-results (tf fn)
> >    (tf-traverse tf
> >      (lambda (tf)
> >        (dolist (d (derivations tf))
> >          (dolist (result (results d))
> >            (funcall fn result))))))
> >
> > Modest edge for Arc, to my eyes. Not a good comparison after all? Unless
> > it turns out that so much code turns out not to benefit from Arc's
> > economies that nothing has been accomplished.
> >
> 
> 3 versions in Clojure for comparison:
> 
> ;for is lazy list comprehension
> ;scan is needed because you are calling f for side-effects
> 
> (defn tf-traverse-results [tf f]
>   (tf-traverse tf
>     (fn [tf]
>       (scan (for [d (derivations tf) result (results d)] (f
> result))))))
> 
> ;doseq might make side-effects more obvious
> 
> (defn tf-traverse-results [tf f]
>   (tf-traverse tf
>     (fn [tf]
>       (doseq r (for [d (derivations tf) result (results d)] result)
> 	 (f r)))))
> 
> ;akin to CL version:
> 
> (defn tf-traverse-results [tf f]
>   (tf-traverse tf
>     (fn [tf]
>        (doseq d (derivations tf)
> 	 (doseq result (results d)
>            (f result))))))
> 
> Rich


Anyone feeling the need to do a SERIES version?
From: Ken Tilton
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <47af8a28$0$25056$607ed4bc@cv.net>
Rainer Joswig wrote:
> In article 
> <····································@v67g2000hse.googlegroups.com>,
>  Rich Hickey <··········@gmail.com> wrote:
> 
> 
>>On Feb 10, 2:18 am, Ken Tilton <···········@optonline.net> wrote:
>>
>>
>>>I should ... oh, cripes, at some point I did enhance tf-traverse to
>>>handle nil sensibly, everybody gets a little shorter:
>>>
>>>(def tf-traverse-results (tf fn)
>>>   (tf-traverse tf
>>>     [each d (derivations _)
>>>         (each result (results d)
>>>           (fn result))])))
>>>
>>>(defun tf-traverse-results (tf fn)
>>>   (tf-traverse tf
>>>     (lambda (tf)
>>>       (dolist (d (derivations tf))
>>>         (dolist (result (results d))
>>>           (funcall fn result))))))
>>>
>>>Modest edge for Arc, to my eyes. Not a good comparison after all? Unless
>>>it turns out that so much code turns out not to benefit from Arc's
>>>economies that nothing has been accomplished.
>>>
>>
>>3 versions in Clojure for comparison:
>>
>>;for is lazy list comprehension
>>;scan is needed because you are calling f for side-effects
>>
>>(defn tf-traverse-results [tf f]
>>  (tf-traverse tf
>>    (fn [tf]
>>      (scan (for [d (derivations tf) result (results d)] (f
>>result))))))
>>
>>;doseq might make side-effects more obvious
>>
>>(defn tf-traverse-results [tf f]
>>  (tf-traverse tf
>>    (fn [tf]
>>      (doseq r (for [d (derivations tf) result (results d)] result)
>>	 (f r)))))
>>
>>;akin to CL version:
>>
>>(defn tf-traverse-results [tf f]
>>  (tf-traverse tf
>>    (fn [tf]
>>       (doseq d (derivations tf)
>>	 (doseq result (results d)
>>           (f result))))))
>>
>>Rich
> 
> 
> 
> Anyone feeling the need to do a SERIES version?

I am waiting for the recursive version -- or is that what the two-labels 
version did, I was laughing to hard to notice. <scrolling back> Nope.

kenny

ps. series is a rare thing in CL I never use. wonder what it does. k

-- 
http://smuglispweeny.blogspot.com/
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius
From: John Thingstad
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <op.t59zsdxput4oq5@pandora.alfanett.no>
P� Sat, 09 Feb 2008 20:53:54 +0100, skrev Ken Tilton  
<···········@optonline.net>:

>
> (defun tf-traverse-results (tf fn)
>    (when tf
>      (tf-traverse tf
>        (lambda (tf)
>          (loop for d in (derivations tf) do
>                (loop for result in (results d)
>                    do (funcall fn result)))))))
>

mapc is your friend here. Arc's map is equivalent to CL's mapcar, but  
since you are not using the result why waste time consing. (In Arc you  
have no choice.)

(defun tf-traverse-results (tf result-fn)
   (labels ((on-results (d)
              (mapc (lambda (r) (funcall result-fn  r)) (results d)))
            (on-derivations (tf)
              (mapc #'on-results (derivations tf))))
     (when tf (tf-traverse tf (on-derivations tf)))))

> It was a random choice, but the tight packing of all these iterations  
> and 1st-class functions might be confusing the issue. Anyway...

Well I like it better.

>
> The CL versions are both trivial to read and even make obvious the  
> organization of the data structures if one did not know them, which  
> could be me because who can remember all that in a huge application?
>
> I am not sure on the Arc version since I am still new to reading it, but  
> it seems like it would always take more work to unwind in my head. As  
> for the brevity of the denser version, hey, why did God create scroll  
> bars?

Could it be that you are not used to a functional programming style using  
the map family?

--------------
John Thingstad
From: Harald Hanche-Olsen
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <pcozlu9kbje.fsf@shuttle.math.ntnu.no>
+ "John Thingstad" <·······@online.no>:

> mapc is your friend here. Arc's map is equivalent to CL's mapcar, but
> since you are not using the result why waste time consing. (In Arc you
> have no choice.)

But it should be easy enough for a compiler to notice that the value is
not being used and so skip the consing.  Or maybe not so easy, if the
map form is in a tail call, but then one could imagine a calling
convention that is capable of informing the callee that any return value
will be ignored, so that it can decide not to bother building one.  To
be useful, such a facility should work unobtrusively in the background
most of the time.

-- 
* Harald Hanche-Olsen     <URL:http://www.math.ntnu.no/~hanche/>
- It is undesirable to believe a proposition
  when there is no ground whatsoever for supposing it is true.
  -- Bertrand Russell
From: Ken Tilton
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <47af89e1$0$25056$607ed4bc@cv.net>
John Thingstad wrote:
> P� Sat, 09 Feb 2008 20:53:54 +0100, skrev Ken Tilton  
> <···········@optonline.net>:
> 
>>
>> (defun tf-traverse-results (tf fn)
>>    (when tf
>>      (tf-traverse tf
>>        (lambda (tf)
>>          (loop for d in (derivations tf) do
>>                (loop for result in (results d)
>>                    do (funcall fn result)))))))
>>
> 
> mapc is your friend here. Arc's map is equivalent to CL's mapcar, but  
> since you are not using the result why waste time consing. (In Arc you  
> have no choice.)

My bad, I forgot EACH, and it is really bad because as I was writing it 
I had a feeling I was forgetting something so I shoulda checked.

But you are right in re Arc not having the equiv of MAPC. pg's answer 
might be, use EACH.


> 
> (defun tf-traverse-results (tf result-fn)
>   (labels ((on-results (d)
>              (mapc (lambda (r) (funcall result-fn  r)) (results d)))

Not?: (when d
          (funcall result-fn (car d))
          (on-results (cdr d)))

<g>

kenny

-- 
http://smuglispweeny.blogspot.com/
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius
From: Sohail Somani
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <rGtrj.18631$w57.11353@edtnps90>
On Sat, 09 Feb 2008 14:53:54 -0500, Ken Tilton wrote:

> (def tf-traverse-results (tf result-fn)
>    (when tf
>      (tf-traverse tf
>        [map [map result-fn (results _)]
>              (derivations _)]]))

Hi,

Given the following:

(defun |#[]-reader| (s c n)
  (declare (ignore c n))
  (let (forms)
    (do ()
        (nil)
      (let ((form (read s t (values) t)))
        (when (eql form '])
          (return))
        (push form forms)))
    `(lambda (_) (,@(reverse forms)))))

(defparameter *old-readtable* nil)
(defun enable-[]-reader ()
  (setf *old-readtable* *readtable*)
  (setf *readtable* (copy-readtable nil))
  (set-dispatch-macro-character #\# #\[
                                #'|#[]-reader|
                                *readtable*))

(defun disable-[]-reader ()
  (setf *readtable* *old-readtable*))

The CL version is (probably):

(defun tf-traverse-results (tf result-fn)
  (when tf
    (tf-traverse tf
      #[ mapc #[ mapc result-fn (results _) ]
               (derivations _)]])))
                
Barely tested so it is probably wrong but I'm not sure what you were 
trying to show. I do appreciate the syntactic niceness of #[ though.

Could you elaborate your point a little?

-- 
Sohail Somani
http://uint32t.blogspot.com
From: Ken Tilton
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <47ae8355$0$7882$607ed4bc@cv.net>
Sohail Somani wrote:
> On Sat, 09 Feb 2008 14:53:54 -0500, Ken Tilton wrote:
> 
> 
>>(def tf-traverse-results (tf result-fn)
>>   (when tf
>>     (tf-traverse tf
>>       [map [map result-fn (results _)]
>>             (derivations _)]]))
> 
> 
> Hi,
> 
> Given the following:

Please don't encourage Costanza, he's bad enough as it is.

> 
> (defun |#[]-reader| (s c n)
>   (declare (ignore c n))
>   (let (forms)
>     (do ()
>         (nil)
>       (let ((form (read s t (values) t)))
>         (when (eql form '])
>           (return))
>         (push form forms)))
>     `(lambda (_) (,@(reverse forms)))))
> 
> (defparameter *old-readtable* nil)
> (defun enable-[]-reader ()
>   (setf *old-readtable* *readtable*)
>   (setf *readtable* (copy-readtable nil))
>   (set-dispatch-macro-character #\# #\[
>                                 #'|#[]-reader|
>                                 *readtable*))
> 
> (defun disable-[]-reader ()
>   (setf *readtable* *old-readtable*))
> 
> The CL version is (probably):
> 
> (defun tf-traverse-results (tf result-fn)
>   (when tf
>     (tf-traverse tf
>       #[ mapc #[ mapc result-fn (results _) ]
>                (derivations _)]])))
>                 
> Barely tested so it is probably wrong but I'm not sure what you were 
> trying to show. I do appreciate the syntactic niceness of #[ though.
> 
> Could you elaborate your point a little?
> 

Sure! Can you elaborate on what part of...

> The CL versions are both trivial to read and even make obvious the
organization of the data structures if one did not know them, which
could be me because who can remember all that in a huge application?
> 
> I am not sure on the Arc version since I am still new to reading it,
but it seems like it would always take more work to unwind in my head.
As for the brevity of the denser version, hey, why did God create scroll
bars?

...you did not understand? All you have done is an Arc-alike, throwing 
yourself into the second paragraph.

All I can think (and I am guessing here, so apos if I get ths wrong) is 
that this group is being as dense as usual and has misconstrued my 
openness to Arc and condemnation of cll prejudice against Arc as in any 
way shape or form indicating a preference for Arc. So not having 
ascended to bradshawian pure lightness you have misread as praise an 
expressed concern about the readability and even writability of Arc!

Juuust peachy. Funny how emotions get in the way of reading 
comprehension. Here, second chance (I took out some of the big words):

> The CL versions are both trivial to read and even make obvious the
> organization of the data structures...it seems like it would always
take more work to unwind [the Arc versions] in my head.

A corrollary on the utter irrelevance of your post: is it meant to be a 
scoop that CL can use macrology and the reader to replicate some 
Arc-isms? Oh, my. Hello? if*? Of course Foderaro went loopier to support 
implicit progn, but as good little functional programmers (I have been 
studying since Thingstad recommended remedial attention) we should not 
be progning all that much.

kenny

ps. Nice job on the code! Two honest Qs. You can't just do it with the 
[, you need the #[? I just woke up, can't remember if we use [ for 
anything in CL. Second, you need the space after the [? k

-- 
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius
From: Sohail Somani
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <fXwrj.18661$w57.10182@edtnps90>
On Sat, 09 Feb 2008 23:53:43 -0500, Ken Tilton wrote:

> Sure! Can you elaborate on what part of...
> 
>> The CL versions are both trivial to read and even make obvious the
> organization of the data structures if one did not know them, which
> could be me because who can remember all that in a huge application?
>> 
>> I am not sure on the Arc version since I am still new to reading it,
> but it seems like it would always take more work to unwind in my head.
> As for the brevity of the denser version, hey, why did God create scroll
> bars?
> 
> ...you did not understand? All you have done is an Arc-alike, throwing
> yourself into the second paragraph.

I was just unsure given your "Arc is cool" posts what you were trying to 
accomplish. Reading this one in isolation has the intended effect though.

> All I can think (and I am guessing here, so apos if I get ths wrong) is
> that this group is being as dense as usual and has misconstrued my
> openness to Arc and condemnation of cll prejudice against Arc as in any
> way shape or form indicating a preference for Arc. So not having
> ascended to bradshawian pure lightness you have misread as praise an
> expressed concern about the readability and even writability of Arc!

The answer is yes.

> Juuust peachy. Funny how emotions get in the way of reading
> comprehension. Here, second chance (I took out some of the big words):

Thanks for dumbing it down!
 
>> The CL versions are both trivial to read and even make obvious the
>> organization of the data structures...it seems like it would always
> take more work to unwind [the Arc versions] in my head.
>
> A corrollary on the utter irrelevance of your post: is it meant to be a
> scoop that CL can use macrology and the reader to replicate some Arc-
> isms?
[snip] 

Corollary? That is a mighty big word. I can't lift it up. As to the 
reason for the post, I needed to distract myself for a few minutes. Did 
the job quite well for me!

> ps. Nice job on the code! Two honest Qs. You can't just do it with the
> [, you need the #[? I just woke up, can't remember if we use [ for
> anything in CL. Second, you need the space after the [? k

I think you could do with just [. You need a space before the ] because 
as I've written the code, #[foo bar] gets read as: #[, foo, bar]. I don't 
think you need a space after the #[ since that is the dispatch character.

To really fix the code, I think you would need to check each symbol as it 
is read to see if the last character is ] in the symbol-name.

PS: Are you kidding about nice job?

-- 
Sohail Somani
http://uint32t.blogspot.com
From: Ken Tilton
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <47aeacac$0$15181$607ed4bc@cv.net>
Sohail Somani wrote:
> I was just unsure given your "Arc is cool" posts what you were trying to 
> accomplish. Reading this one in isolation has the intended effect though.

The next question is whether I ever said "Arc is cool". I thought I 
said, "People who diss Arc without trying it are daft because this is 
the kinda thing ya gotta live with to assess." You projected into that 
that I was defending Arc out of affection for it, when all my words did 
was chastise prejudice. I feel a Naggum coming on. Before you contradict 
me or challenge me or quote me, please make sure you are not in fact 
talking about an inferior model of me rooting around somewhere in your 
cortex (and what a scary image that is).

> I think you could do with just [. You need a space before the ] because 
> as I've written the code, #[foo bar] gets read as: #[, foo, bar]. I don't 
> think you need a space after the #[ since that is the dispatch character.

<g>

  "As I have written the code" is the issue. Are you telling me I need a 
space before all my right parens? No wonder I can't finish this Algebra 
program.

> PS: Are you kidding about nice job?

No, it looked like you made a solid effort, albeit "barely tested so it 
is probably wrong", and it is the kind of thing -- once polished -- that 
could be an important part of any Arc/CL discussion. Don't forget, we 
will soon have a ricochet effect as people quickly get fired up over 
Lisp thanks to Arc and just as quickly want something industrial 
strength and you can be part of a welcoming committee.

Hey, you should start a project to replicate as much of Arc as possible 
"On Common Lisp", just not in a way that hides CL, ie, do not redefine 
IF. IF* is taken, but you can find something (IF^? That circumflex looks 
like an arch) then use it to differentiat map and others as well. A lot 
of it is already done, grab the source from On Lisp. Due Monday.


kenny

-- 
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius
From: Sohail Somani
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <Ofyrj.18663$w57.5731@edtnps90>
On Sun, 10 Feb 2008 02:50:00 -0500, Ken Tilton wrote:

> Sohail Somani wrote:
>> I was just unsure given your "Arc is cool" posts what you were trying
>> to accomplish. Reading this one in isolation has the intended effect
>> though.
> 
> The next question is whether I ever said "Arc is cool". I thought I
> said, "People who diss Arc without trying it are daft because this is
> the kinda thing ya gotta live with to assess." You projected into that
> that I was defending Arc out of affection for it, when all my words did
> was chastise prejudice. 

You've got it!

>> I think you could do with just [. You need a space before the ] because
>> as I've written the code, #[foo bar] gets read as: #[, foo, bar]. I
>> don't think you need a space after the #[ since that is the dispatch
>> character.
> 
> <g>
> 
>   "As I have written the code" is the issue. Are you telling me I need a
> space before all my right parens? No wonder I can't finish this Algebra
> program.

Yeah, I don't know how that works... Is ) a dispatch character? If so, 
then something similar would need to be done to the posted code. Maybe 
you haven't finished the Algebra program because you make too much money 
doing something else.

>> PS: Are you kidding about nice job?
> 
> No, it looked like you made a solid effort, albeit "barely tested so it
> is probably wrong", and it is the kind of thing -- once polished -- that
> could be an important part of any Arc/CL discussion. Don't forget, we
> will soon have a ricochet effect as people quickly get fired up over
> Lisp thanks to Arc and just as quickly want something industrial
> strength and you can be part of a welcoming committee.

Do you really believe that last part? I'm not sure.

> Hey, you should start a project to replicate as much of Arc as possible
> "On Common Lisp", just not in a way that hides CL, ie, do not redefine
> IF. IF* is taken, but you can find something (IF^? That circumflex looks
> like an arch) then use it to differentiat map and others as well. A lot
> of it is already done, grab the source from On Lisp. Due Monday.

I did it last week but signed a NDA with myself.

-- 
Sohail Somani
http://uint32t.blogspot.com
From: Leslie P. Polzer
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <1b2fab86-9386-4936-877b-b6bcfbcf2450@v46g2000hsv.googlegroups.com>
Why would anyone in this group waste so much time with Arc?
Honestly, I don't get it.

Kenny, get your bottom up and work on your Algebra software so we'll
see a release before 2012.

  Leslie
From: Slobodan Blazeski
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <d2b5eda6-fcfc-4d6b-a6b4-65cafed9bc40@e23g2000prf.googlegroups.com>
On Feb 10, 10:37 am, "Leslie P. Polzer" <·············@gmx.net> wrote:
> Why would anyone in this group waste so much time with Arc?
> Honestly, I don't get it.

I've checked Arc and though I have  a great respect for PG, the author
of 2 of my favourite books especially On lisp and a lot of great
esseys I woould skip Arc.
Here's why? I'm interested in learning new languages because they
change the way I think.
There's nothing new that I could learn from Arc that I've never
encountered in lisp or scheme.
Ok he polished a little, a has some preferences that somebody could or
couldn't accept but that's it.
In game development slang if people bought Halo 3 they won't buy Halo
3.1, no way. Gamers want brand new story, cooler graphic engine , more
realistic physics, many new weapons   etc to have even a chance to
take their money. Arc looks more like a personal patch to scheme, like
that McBride with single namespace lisp.
I recently learned some Prolog, and although the language sucks,
especially his syntax it has 3 cool ideas.
All the programming is consisted of rule, you can take that facts are
degenerated rules.
Built in unification. Built in nondeterminism. Built in database.
So for example you could have :
(addrule (small-prime 2))
(addrule (small-prime 3))
(addrule (small-prime 5))
(addrule (small-prime 7))
or you can do :
(defrule (small-prime ?x)  (and (prime-p ?x) (< x 10)))
The above idea about rules and facts being the same is enough for me
to recommend prolog as worthy experience.And I would like to have
those ideas , not prolog, integrated in lisp.
If pg/rm can't offer me something that will strike me as novel ideas,
or integration fo some idea that wasn't present in lisp already, I
wouldn't learn experimental language with zero libraries.

cheers
Slobodan
From: Leslie P. Polzer
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <296bd1c0-4498-4d24-92d8-d27d63a62c30@d70g2000hsb.googlegroups.com>
> Slobodan

I second your statements. Couldn't have pointed that out better
myself.

  Leslie
From: Ken Tilton
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info  inside)
Date: 
Message-ID: <47aedba2$0$15201$607ed4bc@cv.net>
Leslie P. Polzer wrote:
> Why would anyone in this group waste so much time with Arc?
> Honestly, I don't get it.

Actually, I honestly think the burden is on you. Of /course/ a Lisper is 
interested in something that will expand Lisp's mindshare... what 
honestly requires getting is why certain individuals have formed a 
resistance community to piss all over the fun.

What /is/ your problem? A few have almost made explicit a player-hater 
phenomenon -- Qi is OK because Mark is not a rock star, Arc is not OK 
because Graham is. Is it that? Are you just bothered that Arc is getting 
attention because Graham is popular? Has it occurred to you that Graham 
is popular because he is pretty good at what he does, including writing 
great books on Lisp? I mean, it's not like George Foreman Grills or 
anything, which I hear are actually pretty good.

> Kenny, get your bottom up and work on your Algebra software so we'll
> see a release before 2012.

I am committed to pushing whatever I have out the door no matter what it 
is by the end of this month. Or March, of course.

kenny

-- 
http://smuglispweeny.blogspot.com/
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius
From: Pascal Costanza
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info    inside)
Date: 
Message-ID: <6192acF1fmbhfU1@mid.individual.net>
Ken Tilton wrote:

> Qi is OK because Mark is not a rock star, Arc is not OK 
> because Graham is. Is it that? 

No. Qi is ok because Mark actually achieved something very impressive: 
He developed a programmable static type system, something which, to the 
best of my knowledge, didn't exist until Qi, and is far from trivial. Qi 
enables you to develop your own (domain-specific) typing rules, which 
also fits quite well in (part of) the Lisp philosophy.

Qi may or may not be a step forward - it's hard to predict the 
importance of the concepts behind Qi at the current stage, because more 
experience with such systems are necessary first. [1]  Nevertheless, Qi 
certainly brings us closer to seeing what else is possible in 100 years 
from now, because it brings something actually new on the table.


Pascal

[1] Personally, I have my doubts, but that's just a subjective opinion.

-- 
1st European Lisp Symposium (ELS'08)
http://prog.vub.ac.be/~pcostanza/els08/

My website: http://p-cos.net
Common Lisp Document Repository: http://cdr.eurolisp.org
Closer to MOP & ContextL: http://common-lisp.net/project/closer/
From: Ken Tilton
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <47aec37a$0$15170$607ed4bc@cv.net>
Sohail Somani wrote:
> On Sun, 10 Feb 2008 02:50:00 -0500, Ken Tilton wrote:
> 
>>  "As I have written the code" is the issue. Are you telling me I need a
>>space before all my right parens? No wonder I can't finish this Algebra
>>program.
> 
> 
> Yeah, I don't know how that works... Is ) a dispatch character? 

Do I tell you my problems? I think you can google up a c.l.l discussion 
helping Ilias change parens to brackets that would be useful. Maybe 
read-delimited-list?

> If so, 
> then something similar would need to be done to the posted code. Maybe 
> you haven't finished the Algebra program because you make too much money 
> doing something else.

No, it is just frickin hard, and Lisp is making it harder by making it 
easier to... well, I'd say feature creep but this ain't no creep. Still 
having fun with prolog tho creating random problems... f*ck, I wish I 
had used prolog for the math engine, too. I'd use Qi but I do not want 
to encourage Mark's spamming. :)


>>No, it looked like you made a solid effort, albeit "barely tested so it
>>is probably wrong", and it is the kind of thing -- once polished -- that
>>could be an important part of any Arc/CL discussion. Don't forget, we
>>will soon have a ricochet effect as people quickly get fired up over
>>Lisp thanks to Arc and just as quickly want something industrial
>>strength and you can be part of a welcoming committee.
> 
> 
> Do you really believe that last part? I'm not sure.

I'm not sure what you mean by last part, but I guess it does not matter, 
I believe everything. This may help:

    http://smuglispweeny.blogspot.com/

>>Hey, you should start a project to replicate as much of Arc as possible
>>"On Common Lisp", just not in a way that hides CL, ie, do not redefine
>>IF. IF* is taken, but you can find something (IF^? That circumflex looks
>>like an arch) then use it to differentiat map and others as well. A lot
>>of it is already done, grab the source from On Lisp. Due Monday.
> 
> 
> I did it last week but signed a NDA with myself.
> 

No, really, you should. Technically interesting and nicely finite in 
size as projects go, yet instant fame out of all proportion to the 
effort. One thing that would be key would be to learn Arc itself and 
participate on its forum. CLers with a positive frame of mind are over 
there helping Arc noobs with the Lisp and of course mentioning things 
about CL so it is a solid sharing that at the same time quietly reminds 
people where else to look for the charms of Lisp.

kenny

-- 
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius
From: Slobodan Blazeski
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <eb737899-b714-4487-b332-bfa50aac55c2@h11g2000prf.googlegroups.com>
On Feb 10, 10:27 am, Ken Tilton <···········@optonline.net> wrote:
>
> > If so,
> > then something similar would need to be done to the posted code. Maybe
> > you haven't finished the Algebra program because you make too much money
> > doing something else.
>
> No, it is just frickin hard, and Lisp is making it harder by making it
> easier to... well, I'd say feature creep but this ain't no creep. Still
> having fun with prolog tho creating random problems... f*ck, I wish I
> had used prolog for the math engine, too. I'd use Qi but I do not want
> to encourage Mark's spamming. :)
I case you want to prolong theoryalgebra for 2020+ :), you can
consider my language for your project. I call it tulips. It works like
this:
(defrule blogger (kenny))
(addrule blogger (sohail))
(addrule blogger (leslie))

(blogger '?x)
((?x kenny) (?x sohail) (?x leslie))
(blogger '?x 2)
((?x kenny) (?x sohail))
(mapcar #'blogger '(jimmy  sohail leslie john))
(nil t t nil)

(defrule grandfather (?x ?y)
  (and (father ?x ?z)
       (father ?z ?y)))

(addrule grandfather (jim tom))


> I believe everything. This may help:
>
>    http://smuglispweeny.blogspot.com/
Cool start. However I would still prefer theoryalgebra as success
story.
cheers
Slobodan
> kenny
>
> --http://www.theoryyalgebra.com/
From: Sohail Somani
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <e9Hrj.19609$C61.7099@edtnps89>
On Sun, 10 Feb 2008 04:27:18 -0500, Ken Tilton wrote:

> Sohail Somani wrote:

>> Yeah, I don't know how that works... Is ) a dispatch character?
> 
> Do I tell you my problems? 

No, and I would appreciate it remaining this way. I think even Google 
Groups would have a problem with the volume of messages this way.

> I think you can google up a c.l.l discussion
> helping Ilias change parens to brackets that would be useful. Maybe
> read-delimited-list?

Ah, thanks for the pointer.

[snip]
> This may help:
> 
>     http://smuglispweeny.blogspot.com/

Awesome.

>>>Hey, you should start a project to replicate as much of Arc as possible
[snip]
>> I did it last week but signed a NDA with myself.

> No, really, you should. Technically interesting and nicely finite in
> size as projects go, yet instant fame out of all proportion to the
> effort. 
[snip]

I think this would be a good way to learn CL. I might take you up on it.

-- 
Sohail Somani
http://uint32t.blogspot.com
From: Sohail Somani
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <UgIrj.19618$C61.8505@edtnps89>
On Sun, 10 Feb 2008 04:27:18 -0500, Ken Tilton wrote:

>> If so,
>> then something similar would need to be done to the posted code. Maybe
>> you haven't finished the Algebra program because you make too much
>> money doing something else.
> 
> No, it is just frickin hard, and Lisp is making it harder by making it
> easier to... well, I'd say feature creep but this ain't no creep. Still
> having fun with prolog tho creating random problems... f*ck, I wish I
> had used prolog for the math engine, too. I'd use Qi but I do not want
> to encourage Mark's spamming.

Just did some Googling your intended results. Best of luck dude, sounds 
like this can be a killer app.

But really, just release it already. What age group are you looking at? 
Do you think 7 year olds can benefit? I would be happy to try it out on 
my offspring if so. Or I can help you adjust it for this age range in 
exchange for some royalties ;-)

-- 
Sohail Somani
http://uint32t.blogspot.com
From: Kaz Kylheku
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <41935ff0-47dc-49c7-aa64-498adc6319e6@i7g2000prf.googlegroups.com>
On Feb 9, 11:50 pm, Ken Tilton <···········@optonline.net> wrote:
> Sohail Somani wrote:
> > I was just unsure given your "Arc is cool" posts what you were trying to
> > accomplish. Reading this one in isolation has the intended effect though.
>
> The next question is whether I ever said "Arc is cool". I thought I
> said, "People who diss Arc without trying it are daft because this is
> the kinda thing ya gotta live with to assess."

I refuse to live with crap to assess it. Thankfully, I've developed
the ability to absorb a language specification and assess it that way,
as if I had lived with it.

Actually living with every goddamned thing that you are called upon to
assess is intractable. It creates a deep time sink in every direction
you turn.
From: John Thingstad
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <op.t6bxvlgcut4oq5@pandora.alfanett.no>
P� Sun, 10 Feb 2008 20:34:27 +0100, skrev Kaz Kylheku <········@gmail.com>:

>
> I refuse to live with crap to assess it.

> Thankfully, I've developed
> the ability to absorb a language specification and assess it that way,
> as if I had lived with it.
>

Even if you have how would it help you assess Arc which doesn't have one?

> Actually living with every goddamned thing that you are called upon to
> assess is intractable. It creates a deep time sink in every direction
> you turn.

Me I usually just igore them. I try to avoid having strong opinions about  
things I have little knowlege about..

--------------
John Thingstad
From: Pascal Bourguignon
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <87sl01jd6l.fsf@thalassa.informatimago.com>
Sohail Somani <······@taggedtype.net> writes:
>> ps. Nice job on the code! Two honest Qs. You can't just do it with the
>> [, you need the #[? I just woke up, can't remember if we use [ for
>> anything in CL. Second, you need the space after the [? k
>
> I think you could do with just [. You need a space before the ] because 
> as I've written the code, #[foo bar] gets read as: #[, foo, bar]. I don't 
> think you need a space after the #[ since that is the dispatch character.
>
> To really fix the code, I think you would need to check each symbol as it 
> is read to see if the last character is ] in the symbol-name.

IIRC, #\[ and #\{ are reserved to the user.  
clhs read-delimited-list

 (defun \[-reader (stream char)
   (declare (ignore char))
   (read-delimited-list #\] stream))

 (set-macro-character #\[ (function \[-reader))
 (set-macro-character #\] (get-macro-character #\)) nil)


C/USER[32]> '[a b c]
(A B C)

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/
Wanna go outside.
Oh, no! Help! I got outside!
Let me back inside!
From: Sohail Somani
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info inside)
Date: 
Message-ID: <PaHrj.19611$C61.8832@edtnps89>
On Sun, 10 Feb 2008 11:52:50 +0100, Pascal Bourguignon wrote:

> Sohail Somani <······@taggedtype.net> writes:
>>> ps. Nice job on the code! Two honest Qs. You can't just do it with the
>>> [, you need the #[? I just woke up, can't remember if we use [ for
>>> anything in CL. Second, you need the space after the [? k
>>
>> I think you could do with just [. You need a space before the ] because
>> as I've written the code, #[foo bar] gets read as: #[, foo, bar]. I
>> don't think you need a space after the #[ since that is the dispatch
>> character.
>>
>> To really fix the code, I think you would need to check each symbol as
>> it is read to see if the last character is ] in the symbol-name.
> 
> IIRC, #\[ and #\{ are reserved to the user. clhs read-delimited-list
> 
>  (defun \[-reader (stream char)
>    (declare (ignore char))
>    (read-delimited-list #\] stream))
> 
>  (set-macro-character #\[ (function \[-reader)) (set-macro-character #\]
>  (get-macro-character #\)) nil)
> 
> 
> C/USER[32]> '[a b c]
> (A B C)

Cool, thanks!

This message was intentionally mostly quoted.

-- 
Sohail Somani
http://uint32t.blogspot.com
From: Kaz Kylheku
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info 	inside)
Date: 
Message-ID: <e7b47780-c843-428a-8bcc-894418e34610@l16g2000hsh.googlegroups.com>
On Feb 9, 11:53 am, Ken Tilton <···········@optonline.net> wrote:
> I literally grabbed a the first function I saw in my code for an experiment:
>
> ; --- the doc ---
> ; (I just moved the doc down below so one can encounter the code
> ; the normal way we encounter OPC, cold.)
> ;
> ; --- assuming like most yobs you haven't even looked at Arc ---
> ; CL: (mapcar (lambda (x) (mod x 42)) y)
> ; Arc: (map [mod _ 42] y) or (map (fn (x) (mod x 42)) y)
>
> I'll show the Arc version first cuz I think it is more obscure and I
> want you to see it before the CL "dummies" version(s) makes it obvious
> what is going on:
>
> ; --- Arc version -----------
> ;
> (def tf-traverse-results (tf result-fn)
>    (when tf
>      (tf-traverse tf
>        [map [map result-fn (results _)]
>              (derivations _)]]))
                               ^
Wtf? Does Arc let you match an opening ( with a closing ]?

Common Lisp:

(defun tf-traverse-results (tf result-fn)
  (when tf
     (tf-traverse tf
        [mapc [mapc result-fn (results _)]
              (derivations _)])))

The trivial read macro which transforms [X ...] into (lambda (_)
X ...) is left as an exercise.

If you want to make point about brevity, how about designing TF-
TRAVERSE so that it does the right thing if TF is NIL?

Then we're down to:

(defun tf-traverse-results (tf result-fn)
  (tf-traverse tf
     [mapc [mapc result-fn (results _)]
           (derivations _)]))
From: Ken Tilton
Subject: Re: DON'T READ IF YOU NEED TO KEEP YOUR DEAD IN THE SAND (Arc info  inside)
Date: 
Message-ID: <47af8897$0$25056$607ed4bc@cv.net>
Kaz Kylheku wrote:
> On Feb 9, 11:53 am, Ken Tilton <···········@optonline.net> wrote:
> 
>>I literally grabbed a the first function I saw in my code for an experiment:
>>
>>; --- the doc ---
>>; (I just moved the doc down below so one can encounter the code
>>; the normal way we encounter OPC, cold.)
>>;
>>; --- assuming like most yobs you haven't even looked at Arc ---
>>; CL: (mapcar (lambda (x) (mod x 42)) y)
>>; Arc: (map [mod _ 42] y) or (map (fn (x) (mod x 42)) y)
>>
>>I'll show the Arc version first cuz I think it is more obscure and I
>>want you to see it before the CL "dummies" version(s) makes it obvious
>>what is going on:
>>
>>; --- Arc version -----------
>>;
>>(def tf-traverse-results (tf result-fn)
>>   (when tf
>>     (tf-traverse tf
>>       [map [map result-fn (results _)]
>>             (derivations _)]]))
> 
>                                ^
> Wtf? Does Arc let you match an opening ( with a closing ]?

No, I was editing in email. Or maybe ACL, which does happily pair 
(highlighting-wise) a closing parens with an opening bracket.

> If you want to make point about brevity, how about designing TF-
> TRAVERSE so that it does the right thing if TF is NIL?

Right, and upon inspection it turned out I had done so at some point. 
But part of the exercise was to take real code at random and Just Deal 
With It -- only drug companies are allowed to change their experiments 
midstream to get desired results.

kenny

-- 
http://smuglispweeny.blogspot.com/
http://www.theoryyalgebra.com/

"In the morning, hear the Way;
  in the evening, die content!"
                     -- Confucius