Re: [Haskell-cafe] help with musical data structures

2009-11-16 Thread wren ng thornton

Stephen Tetley wrote:

Hello Mike

A pitch class set represents Z12 numbers so I'd define a Z12 number
type then store it in a list (if you have need a multiset -
duplicates) or Data.Set (if you need uniqueness).


If you want an efficient implementation for *sets* of Z12 numbers I'd 
recommend using bit arithmetic. Pick some Word type with at least 12 
bits and use bit0 to represent including 0 in the set, bit1 to represent 
including 1, bit2 for 2, etc. This can be generalized for any Zn 
provided n is a suitably small number. Z16 may be a good place to start 
if you want wider applicability, though you'd want to wrap that with 
error checking code in order to exclude 12..15.


import Data.Word
import Data.Bits

newtype Z16 = Z16 Word16

z16_0 = 1 `shiftL` 0
z16_1 = 1 `shiftL` 1
z16_2 = 1 `shiftL` 2
...

union= (.|.)
intersection = (.&.)
...

But I don't know whether you need to deal more with sets or with the 
elements therein, so that might reduce the efficiency of this approach.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] help with musical data structures

2009-11-15 Thread Hans Aberg

On 15 Nov 2009, at 12:55, Stephen Tetley wrote:


http://hackage.haskell.org/packages/archive/haskore/0.1/doc/html/Haskore-Basic-Pitch.html
 but maybe it is not what you need, since it distinguishes between  
C sharp

and D flat and so on.



The enharmonic doublings and existing Ord instance make Haskore's
PitchClass a tricky proposition for representing the Serialist's view
of pitch classes. An integer (or Z12) represent would be simpler.


A Z12 representation is really only suitable for serial music, which  
in effect uses 12 scale degrees per octave.



To get pitch names I would recover them with a post-processing step,
spelling pitches with respect to a "scale" (here a SpellingMap):


spell :: SpellingMap -> Pitch -> Pitch


The spell function returns the note in the scale (SpellingMap) if
present, otherwise it returns the original to be printed with an
accidental.

I have my own pitch representation, but a SpellingMap for Haskore  
would be



type SpellingMap = Data.Map PitchClass PitchClass


Scales here are functions that generate SpellingMaps rather than
objects themselves.
The modes and major and minor scales have easy generation as they are
someways rotational over the circle of fifths (I've have implemented a
useful algorithm for this but can't readily describe it[1]). Hijaz and
klezmer fans need to construct their spelling maps by hand.


The pitch and notation systems that Western music uses can be  
described as generated by a minor second m and major second M. Sharps  
and flats alter with the interval M - m. If departing from two  
independent intervals, like a perfect fifth and the octave, then m and  
M can be computed. - I have written some code for ChucK which does  
that and makes them playable on the (typing) keyboard in a two- 
dimensional layout.


The pitch system, which I call a "diatonic pitch system", is then the  
set of combinations p m + q M, where p, q are integers (relative a  
tuning frequency). The sum d = p + q acts a scale degree of the pitch  
system. Sharps and flats do not alter this scale degree. Typical  
common 7 note scales have adjacent scale degrees. This is also true  
for scales like hijaz.


The note name can then be computed as follows:

First one needs (p, q) values representing the note names a b c d e f  
g having scale degrees 0, ..., 6, plus a value for the octave. If  
given an arbitrary combination (p, q), first reduce its octave, and  
then compute its scale degree; subtract the (p, q) value of the note  
name with the same scale degree. There results a note with p + q = 0,  
i.e., p = - q. If q > 0, it is is the number of sharps, if p > 0 it is  
the number of flats.


This method can be generalized. It is not necessary to have 7 notes  
per diapason, and the diapason need not
be the octave. By adding neutral seconds, one can describe more  
general pitch systems (one is enough for Arab, Persian and Turkish  
scales).


  Hans


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] help with musical data structures

2009-11-15 Thread Stephen Tetley
Hi Mike

Try it and time it of course - there are a couple of libraries to help
memo-izing on Hackage. Never having used them, but looking at the docs
neither data-memocombinators or MemoTrie would seem to be
straightforward for Data.Set, so a Word32 or some other number that is
an instance of Bits would be a better choice.

My completely unfounded intuition is what you would gain by
memoization you would loose by packing and unpacking the bit
representation to something that can be read, printed or whatever else
you need to do with it.

The only algorithm I've transcribed for finding prime form is the one
detailed by Paul Nelson here:
http://composertools.com/Theory/PCSets.pdf

This one goes out of Z12 at step 2 but if you were using a 24bit bit
vector (e.g. Word32) it would still cope.

Best wishes

Stephen

2009/11/15 Michael Mossey :
> Hi Stephen,
>
> I will need a function that computes prime (normal?) form, of course, and it
> is just begging to be memoized. I wonder if that is possible with Data.Set,
> or whether it would be much faster using the bit vector representation?
>
> Thanks,
> Mike
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] help with musical data structures

2009-11-15 Thread Michael Mossey

Hi Stephen,

I will need a function that computes prime (normal?) form, of course, and 
it is just begging to be memoized. I wonder if that is possible with 
Data.Set, or whether it would be much faster using the bit vector 
representation?


Thanks,
Mike



Stephen Tetley wrote:

Postscript...

Hi Mike

I rather overlooked your efficiency concerns, however I wouldn't be so
concerned. By the nature of what they represent I wouldn't expect
pitch classes to grow to a size where a bit representation out weighs
the convenience of a list or Data.Set.

By the same reason - I'd only use an array for the pitch matrix if I
felt an interface favouring index-lookup was most 'comfortable'.



Best wishes

Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] help with musical data structures

2009-11-15 Thread Stephen Tetley
2009/11/15 Henning Thielemann :

> In Haskore there is a type for pitch classes:
>
> http://hackage.haskell.org/packages/archive/haskore/0.1/doc/html/Haskore-Basic-Pitch.html
>  but maybe it is not what you need, since it distinguishes between C sharp
> and D flat and so on.

Hi Henning

The enharmonic doublings and existing Ord instance make Haskore's
PitchClass a tricky proposition for representing the Serialist's view
of pitch classes. An integer (or Z12) represent would be simpler.


To get pitch names I would recover them with a post-processing step,
spelling pitches with respect to a "scale" (here a SpellingMap):

> spell :: SpellingMap -> Pitch -> Pitch

The spell function returns the note in the scale (SpellingMap) if
present, otherwise it returns the original to be printed with an
accidental.

I have my own pitch representation, but a SpellingMap for Haskore would be

> type SpellingMap = Data.Map PitchClass PitchClass

Scales here are functions that generate SpellingMaps rather than
objects themselves.
The modes and major and minor scales have easy generation as they are
someways rotational over the circle of fifths (I've have implemented a
useful algorithm for this but can't readily describe it[1]). Hijaz and
klezmer fans need to construct their spelling maps by hand.

Best wishes

Stephen

[1] Code exists here - vis dependencies and scant documentation that
stop it being useful:
http://code.google.com/p/copperbox/source/browse/trunk/bala/Mullein/src/Mullein/Pitch.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] help with musical data structures

2009-11-15 Thread Stephen Tetley
Postscript...

Hi Mike

I rather overlooked your efficiency concerns, however I wouldn't be so
concerned. By the nature of what they represent I wouldn't expect
pitch classes to grow to a size where a bit representation out weighs
the convenience of a list or Data.Set.

By the same reason - I'd only use an array for the pitch matrix if I
felt an interface favouring index-lookup was most 'comfortable'.



Best wishes

Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] help with musical data structures

2009-11-15 Thread Henning Thielemann


On Sat, 14 Nov 2009, Michael Mossey wrote:


I'm pretty new to Haskell so I don't know what kind of data structure I
should use for the following problem. Some kind of arrays, I guess.

One data item, called OrientedPCSet ("oriented pitch class set," a musical
term) will represent a set whose members are from the range of integers 0
to 11. This could probably be represented efficiently as some kind of bit
field for fast comparison.


In Haskore there is a type for pitch classes:
   
http://hackage.haskell.org/packages/archive/haskore/0.1/doc/html/Haskore-Basic-Pitch.html
 but maybe it is not what you need, since it distinguishes between C sharp 
and D flat and so on. It has Ix and Ord instance and thus can be used for 
Array and Map, respectively. Both of them are of course not as efficient 
as a bitset in your case. To this end you might try

   
http://hackage.haskell.org/packages/archive/EdisonCore/1.2.1.3/doc/html/Data-Edison-Coll-EnumSet.html



Another item, PitchMatrix, will be a 2-d matrix of midi pitch numbers.
This matrix will be constructed via a backtracking algortithm with an
evaluation function at each step. It will probably be constructed by
adding one number at a time, starting at the top of a column and working
down, then moving to the next column. This matrix should probably be
implemented as an array of some sort for fast lookup of the item row x,
column y. It doesn't require update/modification to be as fast as lookup,
and it won't get very large, so some sort of immutable array may work.


A MIDI pitch type can be found in
   
http://hackage.haskell.org/packages/archive/midi/0.1.4/doc/html/Sound-MIDI-Message-Channel-Voice.html#t%3APitch
  it also is in Ix class and thus you can define

type PitchMatrix a = Array (Pitch, Pitch) a

The Pitch pair means that you have a pair as array index, thus an 
two-dimensional array. Arrays provide the (//) operator for bundled 
updates. Sometimes it is possible to use the (//) operator or the array 
construction only once, because the order of filling the array is 
determined by data dependencies and laziness. E.g. there is an LU 
decomposition algorithm that does not need array element updates, only a 
clever order of filling the matrix:

  http://hackage.haskell.org/packages/archive/dsp/0.2.1/doc/html/Matrix-LU.html


You may be also interested in the haskell-art mailing list in order to 
discuss musical experiments:

  http://lists.lurk.org/mailman/listinfo/haskell-art

See also
  http://www.haskell.org/haskellwiki/Category:Music
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] help with musical data structures

2009-11-15 Thread Stephen Tetley
Hello Mike

A pitch class set represents Z12 numbers so I'd define a Z12 number
type then store it in a list (if you have need a multiset -
duplicates) or Data.Set (if you need uniqueness).

Having a Z12 numeric type isn't the full story, some operations like
finding prime form have easier algorithms if they are transitory -
i.e. they go out of Z12 to the integers and back.

You might want to look at Richard Bird's Sudoko solver for the other
problem (slides and the code are a web search away) which takes a very
elegant look at a matrix problem.

Below is a Z12 modulo I made earlier - adding QuickCheck tests would
have been wise (also I seem to remember there is a pitch class package
on Hackage):


-- Show instance is hand written to escape constructor noise
-- It seemed useful to have mod12 as a shortcut - tastes may vary
-- The Modulo12 coercion type class is a bit extraneous (fromInteger
which suffice).
-- I use it to allay coercion warnings in other modules


module Z12
  (
  -- * Integers mod 12
Z12
  -- * Integral coercion
  , Modulo12(..)

  , mod12

  ) where

-- Data types

newtype Z12 = Z12 Int
  deriving (Eq,Ord)



class Modulo12 a where
  fromZ12 :: Z12 -> a
  toZ12   :: a  -> Z12



instance Modulo12 Int where
  fromZ12 (Z12 i) = i
  toZ12 i = Z12 $ mod i 12

instance Modulo12 Integer where
  fromZ12 (Z12 i) = fromIntegral i
  toZ12 i = Z12 $ fromIntegral $ mod i 12





instance Show Z12 where
  showsPrec p (Z12 i) = showsPrec p i


-- Num Instances

liftUZ12 :: (Int -> Int) -> Z12 -> Z12
liftUZ12 op (Z12 a) = Z12 $ mod (op a) 12

liftBZ12 :: (Int -> Int -> Int) -> Z12 -> Z12 -> Z12
liftBZ12 op (Z12 a) (Z12 b) = Z12 $ mod (a `op` b) 12

instance Num Z12 where
  (+) = liftBZ12 (+)
  (-) = liftBZ12 (-)
  (*) = liftBZ12 (*)
  negate= liftUZ12 negate
  fromInteger i = Z12 $ (fromInteger i) `mod` 12
  signum _  = error "Modular numbers are not signed"
  abs _ = error "Modular numbers are not signed"




mod12 :: Integral a => a -> a
mod12 = (`mod` 12)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] help with musical data structures

2009-11-14 Thread Michael Mossey
I'm pretty new to Haskell so I don't know what kind of data structure I
should use for the following problem. Some kind of arrays, I guess.

One data item, called OrientedPCSet ("oriented pitch class set," a musical
term) will represent a set whose members are from the range of integers 0
to 11. This could probably be represented efficiently as some kind of bit
field for fast comparison.

Another item, PitchMatrix, will be a 2-d matrix of midi pitch numbers.
This matrix will be constructed via a backtracking algortithm with an
evaluation function at each step. It will probably be constructed by
adding one number at a time, starting at the top of a column and working
down, then moving to the next column. This matrix should probably be
implemented as an array of some sort for fast lookup of the item row x,
column y. It doesn't require update/modification to be as fast as lookup,
and it won't get very large, so some sort of immutable array may work.

Thanks,
Mike



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe