From: LuisGLopez
Subject: Any leak in my first macro? :)
Date: 
Message-ID: <1138503743.780212.87990@g14g2000cwa.googlegroups.com>
Hi!

I'm happy... I *think* I could achieve my first macro!!!

For an app I'm trying to do, I need to translate a list of notes in a
list of numbers; I mean this:

(do do# re re#...) -> (0 1 2 3...)

First I thought in this for a beginning:

(defparameter *scale* '(do do# re re# mi fa fa# sol sol# la la# si))
(position 'do *scale*) -> 0

But then I thought that some people would like to enter equivalent
names like reb (=do#), so I would need this:

(defparameter *scale* '(do do# re re# mi fa fa# sol sol# la la# si))
(defparameter *scale2* '(do reb re mib mi fa solb sol lab la sib si))
(or (position 'mib *scale*) (position 'mib *scale2*)) -> 3

And then I thought there *should* be some way to say "find the position
of this element in these lists"... and I did this:

(defmacro position-in-lists (element &rest lists)
  `(or ,@(loop for lst in lists collect
	       `(position ,element ,lst))))

And I think it works!!!

CL-USER> (position-in-lists 'mib *scale* *scale2*)
3

But I'm not sure if I'm missing something... should any variable be
gensym'd?

Thank you very much,

Luis.

From: ·······@gmail.com
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1138506501.159162.157360@g47g2000cwa.googlegroups.com>
LuisGLopez wrote:
[...]
> And then I thought there *should* be some way to say "find the position
> of this element in these lists"... and I did this:
>
> (defmacro position-in-lists (element &rest lists)
>   `(or ,@(loop for lst in lists collect
> 	       `(position ,element ,lst))))

This can easily be a function instead:

CL-USER> (defun position-in-lists (element &rest lists)

           (some (lambda (list)

                   (position element list))

                 lists))

CL-USER> (position-in-lists 'mib *scale* *scale2*)

3

Paul Khuong
From: Tayssir John Gabbour
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1138514129.573125.272770@g47g2000cwa.googlegroups.com>
LuisGLopez wrote:
> But then I thought that some people would like to enter equivalent
> names like reb (=do#), so I would need this:
>
> (defparameter *scale* '(do do# re re# mi fa fa# sol sol# la la# si))
> (defparameter *scale2* '(do reb re mib mi fa solb sol lab la sib si))
> (or (position 'mib *scale*) (position 'mib *scale2*)) -> 3
>
> And then I thought there *should* be some way to say "find the position
> of this element in these lists"... and I did this:
>
> (defmacro position-in-lists (element &rest lists)
>   `(or ,@(loop for lst in lists collect
> 	       `(position ,element ,lst))))
>
> And I think it works!!!
>
> CL-USER> (position-in-lists 'mib *scale* *scale2*)
> 3
>
> But I'm not sure if I'm missing something... should any variable be
> gensym'd?

Fortunately your macro appears technically sound, but you really just
want a function:

(defun position-in-lists (element &rest lists)
  (loop for list in lists
        thereis (position element list)))

The THEREIS clause of loop does what you want.

(This is still cause for celebration, as probably everyone writes
unnecessary macros at first, in the same way many binge on alcohol
after being artificially deprived for so long...)

Tayssir
From: Coby Beck
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <8FXCf.132537$AP5.23210@edtnps84>
"LuisGLopez" <············@gmail.com> wrote in message 
····························@g14g2000cwa.googlegroups.com...
> (defmacro position-in-lists (element &rest lists)
>  `(or ,@(loop for lst in lists collect
>        `(position ,element ,lst))))
>
> And I think it works!!!
>
> CL-USER> (position-in-lists 'mib *scale* *scale2*)
> 3
>
> But I'm not sure if I'm missing something... should any variable be
> gensym'd?

Hi Luis,

Here's a good rule of thumb: if every argument to your macro is evaluated 
during expansion then it is probably a function.  Perhaps you ran into the 
problem of not being able to apply OR or AND?  Check out SOME and EVERY.

-- 
Coby Beck
(remove #\Space "coby 101 @ bigpond . com")
From: verec
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <43dc7c98$0$87296$5a6aecb4@news.aaisp.net.uk>
On 2006-01-29 03:02:23 +0000, "LuisGLopez" <············@gmail.com> said:

> Hi!
> 
> I'm happy... I *think* I could achieve my first macro!!!
> 
> For an app I'm trying to do, I need to translate a list of notes in a
> list of numbers; I mean this:
> 
> (do do# re re#...) -> (0 1 2 3...)
> 
> First I thought in this for a beginning:
> 
> (defparameter *scale* '(do do# re re# mi fa fa# sol sol# la la# si))
> (position 'do *scale*) -> 0
> 
> But then I thought that some people would like to enter equivalent
> names like reb (=do#), so I would need this:
> 
> (defparameter *scale* '(do do# re re# mi fa fa# sol sol# la la# si))
> (defparameter *scale2* '(do reb re mib mi fa solb sol lab la sib si))
> (or (position 'mib *scale*) (position 'mib *scale2*)) -> 3
> 
> And then I thought there *should* be some way to say "find the position
> of this element in these lists"... and I did this:
> 
> (defmacro position-in-lists (element &rest lists)
>   `(or ,@(loop for lst in lists collect
> 	       `(position ,element ,lst))))
> 
> And I think it works!!!
> 
> CL-USER> (position-in-lists 'mib *scale* *scale2*)
> 3
> 
> But I'm not sure if I'm missing something... should any variable be
> gensym'd?
> 
> Thank you very much,
> 
> Luis.

Just a couple of points.

- you forgot about fab(=mi) and dob(=si) that do occur
  in real life

- since your only problem seems to be to associate a symbol
  such as 'fa# with its rank on a 12 steps scale, this
  is crying for a hash-map, isn't it?

CL-USER 1 > (setf *notes-to-rank* (make-hash-table))    =>  #<EQL Hash 
Table{0} 10FB877F>
CL-USER 4 > (setf (gethash 'do *notes-to-rank*) 0)      =>  0
CL-USER 5 > (setf (gethash 'do# *notes-to-rank*) 1)     =>  1
CL-USER 6 > (setf (gethash 'reb *notes-to-rank*) 1)     =>  1

CL-USER 7 > (defun get-pos(note)
              (gethash note *notes-to-rank*))

CL-USER 8 > (get-pos 'do)                               =>  0 T
CL-USER 9 > (get-pos 'reb)                              =>  1 T
CL-USER 10 > (get-pos 'fa##)                            =>  NIL NIL
--
JFB
From: LuisGLopez
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1138534567.588017.94830@z14g2000cwz.googlegroups.com>
verec wrote:
> On 2006-01-29 03:02:23 +0000, "LuisGLopez" <············@gmail.com> said:
> - since your only problem seems to be to associate a symbol
>   such as 'fa# with its rank on a 12 steps scale, this
>   is crying for a hash-map, isn't it?

Sounds very good!!! Maybe the only think I don't like is to do all the
(setf... for all the possible notes.

Thank you all for your replies! You all are right; now I see that I
didn't need a macro. It's only that I was very excited when I thought
that the only way to do was with one... like many newbies, I *need* to
write one macro of my own. :) I won't feel a lisper till then.

I'll just have to wait a little more, I think. :)

Thank you again,

Luis.
From: Frank Buss
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1ncsz9xqwh83a.97fvv4p65lxq.dlg@40tude.net>
LuisGLopez wrote:

> Sounds very good!!! Maybe the only think I don't like is to do all the
> (setf... for all the possible notes.

your list is small, so using an association list may be fast enough:

(defconstant +scale+
  '((do . 0)
    (do# . 1)
    (reb . 1)
    (re . 2)
    (re# . 3)
    (mib . 3)))

(defun note-to-index (note)
  (cdr (assoc note +scale+)))

If it is getting to slow, you can convert it to a hashtable:

(defconstant +scale-hash+ (make-hash-table))
(loop for (note . index) in *scale*
      do (setf (gethash note *scale-hash*) index))
(defun note-to-index (note)
  (gethash note +scale-hash+))

-- 
Frank Buss, ··@frank-buss.de
http://www.frank-buss.de, http://www.it4-systems.de
From: LuisGLopez
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1138541907.391997.87960@g44g2000cwa.googlegroups.com>
Frank Buss wrote:
> your list is small, so using an association list may be fast enough:
>

Thank you very much, Frank! :)

Finally, I did my app. It translates a list of notes into its 'interval
vector' representation. It's useful for certain musical analysis.
(more info, here:
http://www.traditionalmusic.co.uk/traditional-music/ency/i.htm

Extract: Interval-vector. (Forte) abbrev. IV (set-theory, nonlinear).
an array of six digits representing the interval-class (ic) content of
a chord, where the first digit indicates the quantity of ic1, the
second digit = the quantity of ic2, the third digit = the quantity of
ic3, the fourth digit = the quantity of ic4, the fifth digit= the
quantity of ic5, and the sixth digit = the quantity of ic6. E.g.,
001110 is the IV for a major chord, showing that it contains zero
semitones (ic1), no ic2 (wholetones), one ic3 (minor 3rd), one ic4
(major 3rd), one ic5 (perfect 4th) and no tritones (ic6).)

Here is the code:
---------------
(defconstant +scale+
  '((do   . 0)
    (do#  . 1)
    (reb  . 1)
    (re   . 2)
    (re#  . 3)
    (mib  . 3)
    (mi   . 4)
    (fab  . 4)
    (mi#  . 5)
    (fa   . 5)
    (fa#  . 6)
    (solb . 6)
    (sol  . 7)
    (sol# . 8)
    (lab  . 8)
    (la   . 9)
    (la#  . 10)
    (sib  . 10)
    (si   . 11)))

(defun note-to-index (note)
  (cdr (assoc note +scale+)))

(defun notes-to-indices (notes)
  (remove-duplicates (mapcar #'note-to-index notes)))

(defun interval (note1 note2)
  (let ((dif (abs (- note1 note2))))
    (if (<= dif 6)
	dif
	(- 12 dif))))

(defun ivec (notes)
  (labels ((compute (lst ivec)
	     (if (null lst)
		 ivec
		 (let ((note  (car lst))
		       (lt    (cdr lst)))
		   (loop for nt in lt do
			 (incf (elt ivec (1- (interval note nt)))))
		   (compute lt ivec)))))
    (compute (notes-to-indices notes) (make-array 6
						  :element-type 'integer
						  :initial-element 0))))

It works:

CL-USER> (ivec '(do do# reb))
#(1 0 0 0 0 0)
CL-USER> (ivec '(do re mi si fa# do# mib fa solb sol sol# la la#))
#(12 12 12 12 12 6)
CL-USER> (ivec '(do re mi sol sol# si))
#(2 2 3 4 3 1)
CL-USER> (ivec '(do mi sol))
#(0 0 1 1 1 0)

---------------------------------

I don't like the 'interval' function; there should be a better way to
do it. :-/

But I like the 'labels'!!! :) I don't know if it was necessary, but
wanted to try a new trick. Anyway, please correct me if it was a wrong
use of it.

Thank you very much,

Luis.
From: Wade Humeniuk
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <q_4Df.123207$m05.34599@clgrps12>
LuisGLopez wrote:

> 
> I don't like the 'interval' function; there should be a better way to
> do it. :-/
> 
> But I like the 'labels'!!! :) I don't know if it was necessary, but
> wanted to try a new trick. Anyway, please correct me if it was a wrong
> use of it.
> 

The interval function is fine.  Your ivec is also fine, but here is loop
version, (I just tried to get it as compact as I could).

(defun ivec (notes &aux (ivec (make-array 6 :initial-element 0)))
   (loop for (note . sublist) on (notes-to-indices notes) do
         (dolist (nt sublist) (incf (elt ivec (1- (interval note nt))))))
   ivec)


Wade
From: LuisGLopez
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1138555340.809086.241300@f14g2000cwb.googlegroups.com>
Wade Humeniuk wrote:
> (defun ivec (notes &aux (ivec (make-array 6 :initial-element 0)))
>    (loop for (note . sublist) on (notes-to-indices notes) do
>          (dolist (nt sublist) (incf (elt ivec (1- (interval note nt))))))
>    ivec)

Hmmm....yes-yes-tes... the use of (note . sublist) is *very* clever...
I knew about the destructuring 'option' for loop (thanks to PCL), but I
would have *never* thought about using it that way...
I have to 'meditate' more about the relation between (list... and (cons
(cons (cons..., I think.

Thank you very much!!!

Luis.
From: verec
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <43dce618$0$87297$5a6aecb4@news.aaisp.net.uk>
On 2006-01-29 13:38:27 +0000, "LuisGLopez" <············@gmail.com> said:

> Frank Buss wrote:
>> your list is small, so using an association list may be fast enough:
>> 
> 
> Thank you very much, Frank! :)
> 
> Finally, I did my app. It translates a list of notes into its 'interval
> vector' representation. It's useful for certain musical analysis.
> (more info, here:
> http://www.traditionalmusic.co.uk/traditional-music/ency/i.htm
> 
> Extract: Interval-vector. (Forte) abbrev. IV (set-theory, nonlinear).
> an array of six digits representing the interval-class (ic) content of
> a chord, where the first digit indicates the quantity of ic1, the
> second digit = the quantity of ic2, the third digit = the quantity of
> ic3, the fourth digit = the quantity of ic4, the fifth digit= the
> quantity of ic5, and the sixth digit = the quantity of ic6. E.g.,
> 001110 is the IV for a major chord, showing that it contains zero
> semitones (ic1), no ic2 (wholetones), one ic3 (minor 3rd), one ic4
> (major 3rd), one ic5 (perfect 4th) and no tritones (ic6).)

Hmmm. Interesting. Though a bit surprising/confusing...
001110 seems to indeed correspond to your definition
but I have a hard time seeing it as a major chord. ie,
I don't understand how you can translate

> (ivec '(do mi sol))
> #(0 0 1 1 1 0)

where do mi sol is indeed a major chord, but
do-re# = ic3 = minor 3rd is included.
According to how I understand your definition,
001110 should correspond to do-re#-mi-sol that is,
a mix of major and a minor chord!

I can accept, for the sake of your notation to call
a 5th (=7 halt-tones) a 4th,..

Unless what you are saying is that:
do-mi = major 3rd
mi-sol= minor 3rd
do-sol= your-kind-of-4th (which really is a 5th),
in which case, I guess the translation makes sense,
but the usefulness of having the same information
twice escapes me.

I would have expected:
do-mi-sol = major 3rd + perfect 5th (=4th in your notation)
          = 000110

Would you care to elaborate?

Many thanks
--
JFB 
From: LuisGLopez
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1138556692.024489.105190@z14g2000cwz.googlegroups.com>
verec wrote:

> Unless what you are saying is that:
> do-mi = major 3rd
> mi-sol= minor 3rd
> do-sol= your-kind-of-4th (which really is a 5th),
> in which case, I guess the translation makes sense,
> but the usefulness of having the same information
> twice escapes me.
>
> Would you care to elaborate?

Hi!

Emmm... it's very difficult for me to explain. It is a notation from
Alan Forte. The idea is to 'think' in the chords in a different way
from the 'tonal way of thinking'. In fact, Forte speaks of 'complex',
not 'chord'.

The idea is to think in 'interval classes' first. You have just 6:
unison, minor second, major second, minor third, major third, fourth
and augmented fourth. ALL other intervals can be 'reached' via
transposition and octavation (please, *excuse* my *ugly* english).

Then, the interval vector (ivec for short) is the representation of ALL
the interval classes present in the complex. In a 'tonal major chord'
you have 3 notes -> 3 intervals; exactly the ones you found above.

Now... what would be the ivec for a 'tonal minor chord'? Exactly the
same!!! This can be confusing for 'tonal ears'... and certainly is :).
The fact is that this representation is used to show *different*
musical perceptions. For example, I think you have a piano near you.
Now, find various groups of chords with the same ivec each, with
different octavation and transpotition. I mean, write down several
chords with ivec of (0 0 1 1 1 0), several of (1 0 0 0 1 1), and so on.
First try with 3-notes 'chords'.
Now, *try* them in the piano, several times. You'll begin to find
certain 'family-type' in the chords with the same ivec, mostly
(perhaps) by contrast with others with different ivec's

It may be crazy to find 'familiarity' between a major and a minor
chord... but there is :)
From: verec
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <43dda54f$0$87294$5a6aecb4@news.aaisp.net.uk>
On 2006-01-29 17:44:52 +0000, "LuisGLopez" <············@gmail.com> said:

>> Unless what you are saying is that:
>> do-mi = major 3rd
>> mi-sol= minor 3rd
>> do-sol= your-kind-of-4th (which really is a 5th),
>> in which case, I guess the translation makes sense,
>> but the usefulness of having the same information
>> twice escapes me.
>> 
>> Would you care to elaborate?
> 
> The idea is to think in 'interval classes' first. You have just 6:
> unison, minor second, major second, minor third, major third, fourth
> and augmented fourth. ALL other intervals can be 'reached' via
> transposition and octavation (please, *excuse* my *ugly* english).
> 
> Then, the interval vector (ivec for short) is the representation of ALL
> the interval classes present in the complex. In a 'tonal major chord'
> you have 3 notes -> 3 intervals; exactly the ones you found above.
> 
> Now... what would be the ivec for a 'tonal minor chord'? Exactly the
> same!!! This can be confusing for 'tonal ears'... and certainly is :).
> The fact is that this representation is used to show *different*
> musical perceptions. For example, I think you have a piano near you.
> Now, find various groups of chords with the same ivec each, with
> different octavation and transpotition. I mean, write down several
> chords with ivec of (0 0 1 1 1 0), several of (1 0 0 0 1 1), and so on.
> First try with 3-notes 'chords'.
> Now, *try* them in the piano, several times. You'll begin to find
> certain 'family-type' in the chords with the same ivec, mostly
> (perhaps) by contrast with others with different ivec's
> 
> It may be crazy to find 'familiarity' between a major and a minor
> chord... but there is :)

Interesting. This reminds me of the drills in David Lucas Burge's
relative/perfect picth ear training courses, He likens this kind
of perception to "color hearing".

Thanks for bringing this up. I'll investigate more about Alan Forte.

Many thanks
--
JFB
From: LuisGLopez
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1139087981.037889.5680@f14g2000cwb.googlegroups.com>
verec wrote:
>
> Interesting. This reminds me of the drills in David Lucas Burge's
> relative/perfect picth ear training courses, He likens this kind
> of perception to "color hearing".
>
> Thanks for bringing this up. I'll investigate more about Alan Forte.

Just in case it may be useful (and, of course, if someone is so kind to
point errors or improvements), here is the code so far. Now you can
obtain a list with possible chords for a given IVEC (*all* the possible
ones including 'DO'):

CL-USER> (ivec->chord '(0 0 1 1 1 0))
((DO |RE#| SOL) (DO |RE#| |SOL#|) (DO MI SOL) (DO MI LA) (DO FA |SOL#|)
 (DO FA LA))

If you really need *all* of them, you can use the function transpose:

CL-USER> (transpose '(do mi sol) 7)
(SOL SI RE)

NOTE: the functions 'choose' and 'collect-em' are from an old post in
c.l.l.
(http://groups.google.com/group/comp.lang.lisp/browse_thread/thread/b1112994fa0bd8b8/c429d17d6c5bfc95?q=combinatorics&rnum=4#c429d17d6c5bfc95).
I would *never* be able to do it myself... :-/

I want to thank you all, guys, for your help (which is clear in the
following lines... :))
------------------
(defparameter *notes*
  '((do si#)
    (do# reb)
    (re)
    (re# mib)
    (mi fab)
    (fa mi#)
    (fa# solb)
    (sol)
    (sol# lab)
    (la)
    (la# sib)
    (si dob)))

(defun note->index (note)
  (position note *notes* :test #'member))

(defun notes->indices (notes)
  (remove-duplicates (mapcar #'note->index notes)))

(defun interval (note1 note2)
  (let ((dif (abs (- note1 note2))))
    (if (<= dif 6) dif (- 12 dif))))

(defun chord->ivec (chord)
  (loop for (note . sublist) on (notes->indices chord)
	with ivec = (list 0 0 0 0 0 0) do
	(dolist (nt sublist)
	  (incf (nth (1- (interval note nt)) ivec)))
	finally (return ivec)))

(defparameter *valid-sums* (loop for i from 0 to 11
				 with n = 0
				 collect (incf n i)))

(defun test-valid-sum (ivec)
  (let ((p (position (reduce #'+ ivec) *valid-sums*)))
    (when p (1+ p))))

(defun index->note (index)
  (let ((n (nth index *notes*)))
    (if (listp n) (car n) n)))

(defun indices->notes (indices)
  (remove-duplicates (mapcar #'index->note indices)))

(defun choose (list n function)
  (let ((choice (make-list n)))
    ;; choices are items remaining to choose from
    ;; c-length is the length of choices
    ;; tail is the tail of choice that has yet to be filled in with
valid
    ;;   values
    ;; t-length is the number of items to choose from choice, and
should be
    ;;   = to the length of tail.
    (labels ((choose-1 (choices c-length tail t-length)
               (if (null tail)
                   (funcall function choice)
                 (when (>= c-length t-length)
                   (do* ((l choices (cdr l))
                         (item (car l) (car l))
                         (i c-length (1- i)))
                        ((< i t-length))
                     (setf (car tail) item)
                     (choose-1 (cdr l) (1- i) (cdr tail) (1-
t-length)))))))
       (choose-1 list (length list) choice n))))

(defun collect-em (list n)
  (let ((choices nil))
    (choose list n #'(lambda (choice)
		       (push (indices->notes (append '(0) (copy-list choice)))
choices)))
    choices))

(defun ivec->chord (ivec)
  (let ((cantidad (test-valid-sum ivec))
	(lista nil))
    (if (not cantidad)
	(format t "I'm sorry; impossible IVEC.")
	(let ((posibilidades (collect-em '(1 2 3 4 5 6 7 8 9 10 11) (1-
cantidad))))
	  (dolist (posible posibilidades)
	    (when (equal ivec (chord->ivec posible))
	      (push posible lista)))))
    lista))

(defun transpose (chord intervalo)
  (indices->notes (mapcar #'(lambda (x) (mod (+ x intervalo) 12))
			  (if (numberp (car chord))
			      chord
			      (notes->indices chord)))))
---------------
From: verec
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <43dcc416$0$87297$5a6aecb4@news.aaisp.net.uk>
On 2006-01-29 11:36:07 +0000, "LuisGLopez" <············@gmail.com> said:

> verec wrote:
>> On 2006-01-29 03:02:23 +0000, "LuisGLopez" <············@gmail.com> said:
>> - since your only problem seems to be to associate a symbol
>> such as 'fa# with its rank on a 12 steps scale, this
>> is crying for a hash-map, isn't it?
> 
> Sounds very good!!! Maybe the only think I don't like is to do all the
> (setf... for all the possible notes.

(defvar *notes-to-rank* (make-hash-table))

(defun init-notes ()
  (let ((rank -1))
    (dolist (note '(do do# re re# mi fa fa# sol sol# la la# si))
      (setf (gethash note *notes-to-rank*) (setf rank (1+ rank))))
    (dolist (note '(sib la lab sol solb fa fab mib re reb do dob))
      (setf (gethash note *notes-to-rank*) (setf rank (mod (1- rank) 12))))))

(defun get-note (note)
  (gethash note *notes-to-rank*))

(defun dump ()
  (init-notes)
  (let ((result nil))
    (maphash
     (lambda (key val)
       (pushnew (list key val) result))
     *notes-to-rank*)
    (sort result #'< :key #'cadr)))

CL-USER 11 > (dump)
((DO 0) (REB 1) (DO\# 1) (RE 2) (MIB 3) (RE\# 3) (FAB 4) (MI 4) (FA 5)
 (SOLB 6) (FA\# 6) (SOL 7) (SOL\# 8) (LAB 8) (LA 9) (SIB 10) (LA\# 10)
 (SI 11) (DOB 11))
--
JFB
From: Kaz Kylheku
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1138571664.755783.251760@g44g2000cwa.googlegroups.com>
LuisGLopez wrote:
> Hi!
>
> I'm happy... I *think* I could achieve my first macro!!!
>
> For an app I'm trying to do, I need to translate a list of notes in a
> list of numbers; I mean this:
>
> (do do# re re#...) -> (0 1 2 3...)

It would probably be more useful to define constants instead:

(in-package 'music) ;; define this first

(defconstant do 0)
(defconstant re 2)

Or maybe even special read syntax which could handle a myriad
notations. Hash-comma:

 #,do  ;; read as 0
 #,re   ;; read as 2
 #,fa   ;; read as 7

and also:

  #,I    ;; 0
  #,II   ;; 2
  #,IV  ;; 7

and so on. Hash-semicolon could give chords. Mnemonic: semicolon looks
like two notes stacked above each other:

  #;V7    ;; read as (7 11 14 17)
  #;VM7 ;; (7 11 14 18)

The custom reader would parse symbols like b for flat, # for sharp, +
augmented, - for diminished, 0 for half-diminished, slash for bass
note, "sus" and others.
From: Kaz Kylheku
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1138572262.032724.74250@z14g2000cwz.googlegroups.com>
Kaz Kylheku wrote:
> It would probably be more useful to define constants instead:
>
> (in-package 'music) ;; define this first
>
> (defconstant do 0)
> (defconstant re 2)
>
> Or maybe even special read syntax which could handle a myriad
> notations.

And by the way, I should for the benefits of newbies, have mentioned
some reasons why.

Using a macro to expand special notations is disadvantageous because
that macro must be presented in a context where it is evaluated. So for
instance this won't work

  (defvar *notes* '(do do re# mi))

The macro is in a quoted list, so its evaluation is suppressed.
Constants have the same problem. A list of constants will just be a
list of the symbols, not what the constants represent.

The custom read notation doesn't have this problem, because it is
expanded at read-time, regardless of context:

Thus, given a notation like:

>   #;V7    ;; read as (7 11 14 17)
>   #;VM7 ;; (7 11 14 18)

  (defvar *two-five-one* '(#;IIm7 #;V7 #;IM7))

will nicely be read as:

  (defvar *two-five-one* '((2 5 9 12) (7 11 14 17) (0 4 7 11)))

But of course read notations have disadvantages too.
From: Pascal Bourguignon
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <871wyrrqbu.fsf@thalassa.informatimago.com>
And if you don't like to enter the data in the hash table or type the
a-list, you can just describe it and write the function to do the
rest.

(defparameter *notes*
  '((do si#)
    (do# reb)
    (re)
    (re# mib)
    (mi fab)
    (mi# fa)
    (fa# solb)
    (sol)
    (sol# lab)
    (la)
    (la# sib)
    (si dob)))

Then you can use position:

[5]> (setf note 'sib)
SIB
[6]> (position note *notes* :test (function member))
10

Or you can put them in a hash-table

(defparameter *notes-h* 
      (loop with table = (make-hash-table)
            for i from 0 for nl in *notes* 
            do (loop for n in nl do (setf (gethash n table) i))
            finally (return table)))

and:

    (gethash note *notes-h*)

or of course, you can convert it to a a-list, but then it won't be
more efficient than the original list.

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

What is this talk of 'release'? Klingons do not make software 'releases'.
Our software 'escapes' leaving a bloody trail of designers and quality
assurance people in it's wake.
From: LuisGLopez
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1138555601.718407.89280@g49g2000cwa.googlegroups.com>
Pascal Bourguignon wrote:
> (defparameter *notes*
>   '((do si#)
>     (do# reb)
>     (re)
>     (re# mib)
>     (mi fab)
>     (mi# fa)
>     (fa# solb)
>     (sol)
>     (sol# lab)
>     (la)
>     (la# sib)
>     (si dob)))
(snip)
> [6]> (position note *notes* :test (function member))
> 10
>

Pascal: you are GREAT. *THAT* was what I originally had in my mind!!!!
I wanted to use 'position' but with a list of lists (trees, they are
called?). I see now that the ':test #'member' was the way to express
what I intended in the first time.

Thank you very much!!!

Luis.
From: Pascal Bourguignon
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <87ek2qrbl5.fsf@thalassa.informatimago.com>
"LuisGLopez" <············@gmail.com> writes:

> Pascal Bourguignon wrote:
>> (defparameter *notes*
>>   '((do si#)
>>     (do# reb)
>>     (re)
>>     (re# mib)
>>     (mi fab)
>>     (mi# fa)
>>     (fa# solb)
>>     (sol)
>>     (sol# lab)
>>     (la)
>>     (la# sib)
>>     (si dob)))
> (snip)
>> [6]> (position note *notes* :test (function member))
>> 10
>>
>
> Pascal: you are GREAT. *THAT* was what I originally had in my mind!!!!
> I wanted to use 'position' but with a list of lists (trees, they are
> called?). I see now that the ':test #'member' was the way to express
> what I intended in the first time.

List or tree or another name, it's a question of level of abstraction
and meaning.

For example, a "list" (A B C) is implemented with a tree of CONSes
(just rotate the diagram 45 degrees clocwise):

+-----------------------------------+
| (A B C)                           |
|                                   |
| +---+---+   +---+---+   +---+---+ |
| | * | * |-->| * | * |-->| * |NIL| |
| +---+---+   +---+---+   +---+---+ |
|   |           |           |       |
|   v           v           v       |
| +---+       +---+       +---+     |
| | A |       | B |       | C |     |
| +---+       +---+       +---+     |
+-----------------------------------+


So, a list of list can be said to be a tree of conses, but it's going
too deep in the underlying abstractions layers to my taste.

+-----------------------------------------------+
| ((A 1) (B 2) (C 3))                           |
|                                               |
| +---+---+   +---+---+   +---+---+             |
| | * | * |-->| * | * |-->| * |NIL|             |
| +---+---+   +---+---+   +---+---+             |
|   |           |           |                   |
|   |           |           v                   |
|   |           |         +---+---+   +---+---+ |
|   |           |         | * | * |-->| * |NIL| |
|   |           |         +---+---+   +---+---+ |
|   |           |           |           |       |
|   |           |           v           v       |
|   |           |         +---+       +---+     |
|   |           |         | C |       | 2 |     |
|   |           |         +---+       +---+     |
|   |           v                               |
|   |         +---+---+   +---+---+             |
|   |         | * | * |-->| * |NIL|             |
|   |         +---+---+   +---+---+             |
|   |           |           |                   |
|   |           v           v                   |
|   |         +---+       +---+                 |
|   |         | B |       | 2 |                 |
|   |         +---+       +---+                 |
|   v                                           |
| +---+---+   +---+---+                         |
| | * | * |-->| * |NIL|                         |
| +---+---+   +---+---+                         |
|   |           |                               |
|   v           v                               |
| +---+       +---+                             |
| | A |       | 1 |                             |
| +---+       +---+                             |
+-----------------------------------------------+


Why should we stop here?  Can't we say that this is a bit pattern in
the computer memory?  Or even that it's some class of configurations
of electron states on the silicium substrate?   Why not give the
quantum mechanics formula describing that system?



It would be better to speak of a list of sets of note names, or use
any designator corresponding to the abstraction level of your
language.


Only when you need to implement these abstractions you need to speak
of the underlying subabstractions used to implement them.  

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

HEALTH WARNING: Care should be taken when lifting this product,
since its mass, and thus its weight, is dependent on its velocity
relative to the user.
From: Kaz Kylheku
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <1138573786.407279.267160@g14g2000cwa.googlegroups.com>
> Why should we stop here?  Can't we say that this is a bit pattern in
> the computer memory?

We should stop here because conses are not completely abstracted away.
They "leak" through the abstraction of trees being represented as
lists, so that occasionally we can get useful work done at the "cons
level". Conses are not a sealed-off lower level substrate.

Conses are open and they are as abstract as any other object that we
are dealing with at the high level. They are objects with CAR and CDR
properties that we can nicely retrieve by name. We are blissfully
unaware of representational tricks like CDR coding.

To go any lower though, we have to break through a much stronger seal.

> Or even that it's some class of configurations
> of electron states on the silicium substrate?

The abstraction seal of the instruction set itself prevents us from
depending on that, which allows us to do neat things like emulate an
entire computer on a different one, operating system, device drivers
and all.

So even if you did care about configuration of electron states, there
isn't any way to write code that actually depends on it. And that's a
good reason not to care.

If you are completely sealed off from some lower level, the only reason
to care about its characteristics is performance, and perhaps
reliability.

I care about electrons to the extent that I want to write code that
doesn't waste electricity on a battery-powered device. But for that, I
don't need to know the detailed electronic state of every object.

Sometimes different implemenations of lower levels are almost
identical, except that they have different failure modes. Or some have
failure modes and others don't. So that's another situation where you
have to care, though again, not necessarily about nitty-gritty details.

I would tend to say that these different failure modes break the
abstraction, making it leaky. You may have to code some things quite
differently against, say, a filesystem interface that is made remote
over a network.

So, what I'm trying to say, there are good reasons to go down to
certain particular levels and "arbitrarily" happen to stop there. :)
From: Pascal Bourguignon
Subject: Re: Any leak in my first macro? :)
Date: 
Message-ID: <871wyqr4iy.fsf@thalassa.informatimago.com>
"Kaz Kylheku" <········@gmail.com> writes:

>> Why should we stop here?  Can't we say that this is a bit pattern in
>> the computer memory?
>
> We should stop here because conses are not completely abstracted away.
> They "leak" through the abstraction of trees being represented as
> lists, so that occasionally we can get useful work done at the "cons
> level". Conses are not a sealed-off lower level substrate.
>
> Conses are open and they are as abstract as any other object that we
> are dealing with at the high level. They are objects with CAR and CDR
> properties that we can nicely retrieve by name. We are blissfully
> unaware of representational tricks like CDR coding.
>
> To go any lower though, we have to break through a much stronger seal.

Not really a lot stronger.  To wit, the FGPA and the programmable matter.
http://www.wilmccarthy.com/pmfaq.htm


>> Or even that it's some class of configurations
>> of electron states on the silicium substrate?
>
> The abstraction seal of the instruction set itself prevents us from
> depending on that, which allows us to do neat things like emulate an
> entire computer on a different one, operating system, device drivers
> and all.
>
> So even if you did care about configuration of electron states, there
> isn't any way to write code that actually depends on it. And that's a
> good reason not to care.

Not yet, or not in your Intel Pentium chips.


> [...]
> So, what I'm trying to say, there are good reasons to go down to
> certain particular levels and "arbitrarily" happen to stop there. :)

Right.  My point being that there's often no need not to stay at the
highest abstraction layer.

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

"You cannot really appreciate Dilbert unless you read it in the
original Klingon"