Re: [Haskell-cafe] music-related problem

2010-07-21 Thread Dean Herington

At 11:53 AM -0700 7/4/10, Michael Mossey wrote:

Wondering if I could get some suggestions for coding this problem.

A musical document (or score) consists primarily of a list of 
measures. A measure consists primarily of lists of items. We'll 
consider only one kind of item: a note. Items have a location within 
the measure. A note's
location indicates both where it goes on the page (i.e. a visual 
representation of the score) and what moment in time it begins 
sounding (i.e. rendering the score in sound). My concern here is 
sound.


data Doc = [Measure]

data Loc = ... (represents a location within the musical
document including measure number)


data Measure = Measure [(Loc,Item)]
  -- In the Meausre, we can assume (Loc,Item) are in
  --  ascending order


Notes also have an end, when indicates when in time they stop
sounding. See the 'end' field below. Also note the 'soundedEnd'
 'tieStart' and 'tieStop' fields which I will explain.

data Item = Note
{ pitch :: Pitch
, end :: Loc
, soundedEnd :: Maybe Loc
, tieNext :: Bool
, tiePrior :: Bool
}

There is a concept of tied notes. When two notes are tied
together, their durations are summed and they are sounded
continuously as if one note. Ties have several uses, but one
important one is to make a sound that begins in one measure and
ends in a later measure, by tying notes across measures.

The 'tieNext' field indicates if a note is tied to the following
note (that is, the next note of the same pitch). 'tiePrior'
indicates if tied to immediately prior note of same pitch.

A chain of notes can be tied. Notes in the middle with have
both tieNext and tiePrior set.

In the event a note is within a chain of ties, its 'soundedEnd'
field needs to be computed as Just e where e is the end of the
last note in the chain. This information is useful when rendering
the document as sound.

My problem is:

  - given a Doc in which all fields have been set EXCEPT soundedEnd
(all soundedEnd's are given a default value of Nothing)
  - update those notes in the Doc which need to have soundedEnd set.
This involves chasing down the chain of ties.

I can solve a simpler problem which is

-- Given a note with tieNext set, and a list of notes, find
-- the end Loc of the last note in the chain. Only notes
-- with the same pitch as 'firstNote' are considered when looking
-- for the chain of notes.
computeSoundedEnd :: Item - [Item] - Loc
computeSoundedEnd firstNote notes = compSndEnd (pitch firstNote) notes

compSndEnd :: Pitch - [Item] - Loc
compSndEnd _ [] = error tie chain doesn't come to completion
compSndEnd p (n:ns) = if pitch n == p
then if tieNext n
  then if tiePrior n
then compSndEnd p ns
else error illegal tie chain
  else if tiePrior n
then end n
else error illegal tie chain
else compSndEnd p ns

The thing that is hard for me to understand is how, in a functional
paradigm, to update the entire Doc by chasing down every tie and making
all necessary updates.

Thanks,
Mike



[Sorry to be coming so late to this thread.  I'm catching up on old 
Haskell e-mail.]


I agree with some of the earlier posters that your representation is 
probably more complicated than needed.  (BTW, a graph especially 
seems like overkill.)


Nevertheless, given your representation, `soundedEnd` can be computed 
idiomatically and efficiently in Haskell.  As you showed, computing 
`soundedEnd` for one item depends only on the item and those that 
follow it.  In an imperative language, we would compute the 
`soundedEnd` values from the end to the beginning, storing the 
results as we go.  In Haskell, we can simply use a foldr pattern 
and let lazy evaluation take care of the rest.  (Unfortunately, in 
this case the foldr is not quite so simple, due to the two levels 
of lists--measures and items.)


I simplify the computation of `soundedEnd` by letting it be defined 
always:  For a note whose `tieNext` is `False`, the `soundedEnd` 
value equals the `end` value.  With this approach, `soundedEnd` has 
type `Loc`.  (In fact, its value could be computed (i.e., the thunk 
to evaluate it could be installed) when the item is originally 
created, thanks again to lazy evaluation.)  Also, I eliminate 
`tiePrior` because it's not needed for this demonstration.


Dean


import Ratio

type Duration = Rational  -- Whole note has duration 1.

type Loc = (Int, Duration)

type Pitch = Char  -- for simplicity

data Item = Note
{ pitch :: Pitch
, end :: Loc
, soundedEnd :: Loc
, tieNext :: Bool
}
  deriving (Show, Read)

data Measure = Measure [(Loc, Item)]
  deriving (Show, Read)

type Doc = [Measure]


computeSoundedEnd :: Doc - Doc
computeSoundedEnd measures = foldr 

Re: [Haskell-cafe] music-related problem

2010-07-05 Thread Michael Mossey



erik flister wrote:
 Michael Mossey wrote:


Regarding my use of Rational, it's because I'm representing
*notated* durations or positions in time, which are always fractions
of integers. Suppose I give the command to my program to play via
midi everything from bar 1 beat 1 to bar 2 beat 2 1/2. I want to use
Rational so I know 2 1/2 means 2 1/2 and not 2.499. 



i wasn't suggesting anything Numeric for durations -- those are NoteDurs 
like (Dotted $ Triplet Half).  you don't need numerics until resolving 
temporal locations, like milliseconds or subdivisions of a beat.  those 
may be irrational numbers (consider if the tempo is irrational, or tiny 
random jitter in timing) -- though it's a totally pedantic point on my 
part and realistically won't matter.  ;)
 


We must be addressing different problems. My software doesn't have much 
interest in the concept of eighth notes or dotted notes.


What I want to do is process a musical document to answer questions like this:

  - what notes have onset times between measure 1 beat 1 and measure 1 beat 3?

  - organize the document into verticals: notes that occur at the same 
time in any part


  - what notes finish sounding before measure 4?

In music, the passage of time has two meanings. One meaning is provided by 
the notation: on what beats notes occur and how they last (in terms of 
beats). This is independent of tempo, rit, accel. Call this score time. 
The other meaning is real-world performance in which tempo, rit, accel, 
trills and tremolos are realized. Call this real time.


For the first meaning, my program will find it simple and useful to 
represent time as measure (Int) and beat (Rational --- or perhaps anything 
in class Fractional (I have to study this more)). If I tried to represent 
score time as eighth notes or whatever it would drive me crazy. I have no 
need to do that. (Note that this level of time representation is not 
intended for a human interface.)


Score time can involve fractions composed from numbers greater than 
four---like 7-tuplets. But to my knowledge, there is no way to notate 
something that cannot be represented by a fraction.


Real time is better represented as floating point. It is derived from 
tempos and tempo maps.


Thanks,
Mike





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


[Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey

Wondering if I could get some suggestions for coding this problem.

A musical document (or score) consists primarily of a list of measures. A 
measure consists primarily of lists of items. We'll consider only one 
kind of item: a note. Items have a location within the measure. A note's
location indicates both where it goes on the page (i.e. a visual 
representation of the score) and what moment in time it begins sounding 
(i.e. rendering the score in sound). My concern here is sound.


data Doc = [Measure]

data Loc = ... (represents a location within the musical
document including measure number)


data Measure = Measure [(Loc,Item)]
  -- In the Meausre, we can assume (Loc,Item) are in
  --  ascending order


Notes also have an end, when indicates when in time they stop
sounding. See the 'end' field below. Also note the 'soundedEnd'
 'tieStart' and 'tieStop' fields which I will explain.

data Item = Note
{ pitch :: Pitch
, end :: Loc
, soundedEnd :: Maybe Loc
, tieNext :: Bool
, tiePrior :: Bool
}

There is a concept of tied notes. When two notes are tied
together, their durations are summed and they are sounded
continuously as if one note. Ties have several uses, but one
important one is to make a sound that begins in one measure and
ends in a later measure, by tying notes across measures.

The 'tieNext' field indicates if a note is tied to the following
note (that is, the next note of the same pitch). 'tiePrior'
indicates if tied to immediately prior note of same pitch.

A chain of notes can be tied. Notes in the middle with have
both tieNext and tiePrior set.

In the event a note is within a chain of ties, its 'soundedEnd'
field needs to be computed as Just e where e is the end of the
last note in the chain. This information is useful when rendering
the document as sound.

My problem is:

  - given a Doc in which all fields have been set EXCEPT soundedEnd
(all soundedEnd's are given a default value of Nothing)
  - update those notes in the Doc which need to have soundedEnd set.
This involves chasing down the chain of ties.

I can solve a simpler problem which is

-- Given a note with tieNext set, and a list of notes, find
-- the end Loc of the last note in the chain. Only notes
-- with the same pitch as 'firstNote' are considered when looking
-- for the chain of notes.
computeSoundedEnd :: Item - [Item] - Loc
computeSoundedEnd firstNote notes = compSndEnd (pitch firstNote) notes

compSndEnd :: Pitch - [Item] - Loc
compSndEnd _ [] = error tie chain doesn't come to completion
compSndEnd p (n:ns) = if pitch n == p
then if tieNext n
  then if tiePrior n
then compSndEnd p ns
else error illegal tie chain
  else if tiePrior n
then end n
else error illegal tie chain
else compSndEnd p ns

The thing that is hard for me to understand is how, in a functional
paradigm, to update the entire Doc by chasing down every tie and making
all necessary updates.

Thanks,
Mike








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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Henning Thielemann


On Sun, 4 Jul 2010, Michael Mossey wrote:


I can solve a simpler problem which is

-- Given a note with tieNext set, and a list of notes, find
-- the end Loc of the last note in the chain. Only notes
-- with the same pitch as 'firstNote' are considered when looking
-- for the chain of notes.
computeSoundedEnd :: Item - [Item] - Loc
computeSoundedEnd firstNote notes = compSndEnd (pitch firstNote) notes

compSndEnd :: Pitch - [Item] - Loc
compSndEnd _ [] = error tie chain doesn't come to completion
compSndEnd p (n:ns) = if pitch n == p
   then if tieNext n
 then if tiePrior n
   then compSndEnd p ns
   else error illegal tie chain
 else if tiePrior n
   then end n
   else error illegal tie chain
   else compSndEnd p ns

The thing that is hard for me to understand is how, in a functional
paradigm, to update the entire Doc by chasing down every tie and making
all necessary updates.


You will certainly not be able to make use of foldl or foldr, but you may 
use a manual recursion instead. Just like


computeAllEnds :: [Item] - [Item]
computeAllEnds [] = []
computeAllEnds (x:xs) =
   x{loc = computeSoundedEnd x xs} :
   computeAllEnds xs


Cf. the code in Haskell to turn MIDI events into notes with duration:
  
http://code.haskell.org/haskore/revised/core/src/Haskore/Interface/MIDI/Read.lhs
 However, that's a bit more complicated, since it must respect interim 
tempo changes.

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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Serguey Zefirov
 The thing that is hard for me to understand is how, in a functional
 paradigm, to update the entire Doc by chasing down every tie and making
 all necessary updates.

This looks like one of graph algorithms.

Notes are nodes, ties are arcs. Measures, etc are parts of node label.

soundedEnd property can be computed over this.

Actually, it would be wise to parametrize Item with computed
attributes so that you can clearly distinguish between documents where
soundedEnd is set from documents where it is not.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



Henning Thielemann wrote:


On Sun, 4 Jul 2010, Michael Mossey wrote:


I can solve a simpler problem which is

computeSoundedEnd :: Item - [Item] - Loc
computeSoundedEnd firstNote notes = compSndEnd (pitch firstNote) notes


You will certainly not be able to make use of foldl or foldr, but you 
may use a manual recursion instead. Just like


computeAllEnds :: [Item] - [Item]


What makes it harder than this is that the original document is not a 
single list of Item's--they are broken into measures.


Thanks,
Mike

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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



Serguey Zefirov wrote:

The thing that is hard for me to understand is how, in a functional
paradigm, to update the entire Doc by chasing down every tie and making
all necessary updates.


This looks like one of graph algorithms.

Notes are nodes, ties are arcs. Measures, etc are parts of node label.

soundedEnd property can be computed over this.

Actually, it would be wise to parametrize Item with computed
attributes so that you can clearly distinguish between documents where
soundedEnd is set from documents where it is not.


Ah, this sounds like something I am looking for... parameterizing Item with 
the computed attributes. But I am not clear about what that would look 
like. Would Item have kind * - *? Like


data Item c = Item {pitch::Pitch, end::Loc, computed::c}

?

Thanks,
Mike

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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Henning Thielemann


On Sun, 4 Jul 2010, Michael Mossey wrote:


Serguey Zefirov wrote:

The thing that is hard for me to understand is how, in a functional
paradigm, to update the entire Doc by chasing down every tie and making
all necessary updates.


This looks like one of graph algorithms.

Notes are nodes, ties are arcs. Measures, etc are parts of node label.

soundedEnd property can be computed over this.

Actually, it would be wise to parametrize Item with computed
attributes so that you can clearly distinguish between documents where
soundedEnd is set from documents where it is not.


Ah, this sounds like something I am looking for... parameterizing Item with 
the computed attributes. But I am not clear about what that would look like. 
Would Item have kind * - *? Like


data Item c = Item {pitch::Pitch, end::Loc, computed::c}

?


I like to support static distinction between raw and processed Measure 
data. It makes your code clearer and safer. You may define


data Item end = Item {pitch::Pitch, end::end}

where 'end = Bool' for raw data, and 'end = Loc' for processed data. (I'm 
not entirely sure, I understood your representation properly, thus the 
particular type examples for 'end' may be inappropriate.)

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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Stephen Tetley
If you add Rest as an alternative constructor to Item you should be
able to attribute Items with their duration rather than their onset
position. For most processing this would simplify things.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Henning Thielemann


On Sun, 4 Jul 2010, Stephen Tetley wrote:


If you add Rest as an alternative constructor to Item you should be
able to attribute Items with their duration rather than their onset
position. For most processing this would simplify things.


This is also the way, Haskore organizes its data, but Haskore is also not 
able to manage ties.

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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Serguey Zefirov
 Actually, it would be wise to parametrize Item with computed
 attributes so that you can clearly distinguish between documents where
 soundedEnd is set from documents where it is not.
 Ah, this sounds like something I am looking for... parameterizing Item with
 the computed attributes. But I am not clear about what that would look
 like. Would Item have kind * - *? Like
 data Item c = Item {pitch::Pitch, end::Loc, computed::c}
 ?

Yep.

Item () means there soundEnd isn't set and Item Loc means we computed it.

If you need more computed parameters, just tuple them. ;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey

Hi Stephen,
Thanks for thinking about this. The problem, though, is that notes can 
overlap in time. MusicXML solves this by having not just Note and Rest, but 
Backup and Forward which indicate the current position should be moved 
before interpreting the following data. I'm trying to make it simpler than 
that, by giving a note an absolute location and duration.


-Mike

Stephen Tetley wrote:

If you add Rest as an alternative constructor to Item you should be
able to attribute Items with their duration rather than their onset
position. For most processing this would simplify things.

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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



Henning Thielemann wrote:


On Sun, 4 Jul 2010, Michael Mossey wrote:


Henning Thielemann wrote:


On Sun, 4 Jul 2010, Michael Mossey wrote:


I can solve a simpler problem which is

computeSoundedEnd :: Item - [Item] - Loc
computeSoundedEnd firstNote notes = compSndEnd (pitch firstNote) notes


You will certainly not be able to make use of foldl or foldr, but you 
may use a manual recursion instead. Just like


computeAllEnds :: [Item] - [Item]


What makes it harder than this is that the original document is not a 
single list of Item's--they are broken into measures.


That is, you want a function of type

computeAllEnds :: [Measure] - [Measure]

?


Right, although it occurs to me that it might be superior to represent the 
document as [Item] and give Item a measure-number attribute. There are also 
other measure attributes, so in that case the doc would look like:


data Doc = Doc [MeasureInfo] [Item]

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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Stephen Tetley
On 4 July 2010 21:34, Michael Mossey m...@alumni.caltech.edu wrote:
 Hi Stephen,
 Thanks for thinking about this. The problem, though, is that notes can
 overlap in time.

True - Haskore solves this with the Par operator allowing parallel
musical lines.

ABC and LilyPond have voice overlays - bars are lists of notes, but if
there is more than one musical line then bars can be lists-of-lists of
notes instead.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread erik flister
ties are a presentation-level issue, the underlying (sound) representation
is a single note.  i suggest

Doc = [Note]

where Notes have fields for their measure location and duration.  then
there's no issue with overlapping notes, and start/end times are easy to
calculate.  ties can be calculated easily later for graphical layout by
asking if durations overlap given boundaries (usually measure boundaries,
but also measure centers).

i use a natural rhythm EDSL here:
http://code.google.com/p/h1ccup/source/browse/trunk/theory/haskell/src/LiveCode.hs

here's the rhythm-related part (doesn't handle varying tempo).  it lets you
say things like:

Note {measure = 3, beat = 2, dur = Dotted $ Triplet Quarter}



{-# LANGUAGE ExistentialQuantification, ScopedTypeVariables,
RecordWildCards, RankNTypes #-}

tempo = 200 -- bpm
timeSig   = TimeSig { numBeats = 4
, unit = Quarter
}

data DurBase = Whole | Half | Quarter | Eighth | Sixteenth | ThirtySecond
deriving (Enum, Bounded, Show, Eq)
data ModDur = forall x. NoteDur x = Dotted x | Triplet DurBase

data TimeSig = TimeSig {
  numBeats :: Int
, unit :: DurBase
}

data Note = forall x . NoteDur x = Note {
  midiNum :: Int -- 0-255
, vel :: Int -- 0-255
, chan:: Int -- 0-15
, measure :: Integral a = a
, beat:: Int
, subdiv  :: (Real a, Fractional a) = a -- % of beat
, dur :: x
}

class NoteDur a where
quarters :: (Real x, Fractional x) = a - x

calcDurMS :: (Real x, Fractional x) = a - x
calcDurMS d = 1000 * 60 * beats d / realToFrac tempo

beats :: (Real x, Fractional x) = a - x
beats d = uncurry (/) $ both quarters (d, unit timeSig)
where both (f :: forall a b. (NoteDur a, Real b, Fractional b) = a
- b) (x, y) = (f x, f y)

instance NoteDur DurBase where
quarters x = z where Just z = lookup x . zip [minBound .. maxBound] $
map (fromRational . (2 ^^)) [2, 1 ..]

instance NoteDur ModDur where
quarters (Dotted  x) = quarters x * 3 / 2
quarters (Triplet x) = quarters x * 2 / 3

instance NoteDur Note where
 quarters Note{..} = quarters dur

calcStartMS :: (Real a, Fractional a) = Note - a
calcStartMS n = realToFrac (subdiv n + (fromIntegral $ (measure n * numBeats
timeSig) + beat n)) * (calcDurMS $ unit timeSig)

measureMS :: (Real a, Fractional a) = a
measureMS = calcStartMS Note { measure = 1
 , beat= 0
 , subdiv  = 0
 , midiNum = undefined
 , vel = undefined
 , chan= undefined
 , dur = undefined :: DurBase -- ugh
 }

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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



erik flister wrote:
ties are a presentation-level issue, the underlying (sound) 
representation is a single note.  i suggest


Doc = [Note]

where Notes have fields for their measure location and duration.  then 
there's no issue with overlapping notes, and start/end times are easy to 
calculate.  ties can be calculated easily later for graphical layout by 
asking if durations overlap given boundaries (usually measure 
boundaries, but also measure centers).



Hi erik,
I will look at your EDSL. However, I am dealing with ties because I am 
converting a MusicXML document into a more natural form for my purposes. 
The initial form of the document will have tied notes (as it comes that way 
from MusicXML), and I want to convert that into a form that makes it 
possible to ignore ties and see notes as having a single duration.


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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



erik flister wrote:

I am dealing with ties because I am converting a MusicXML document
into a more natural form for my purposes. The initial form of the
document will have tied notes (as it comes that way from MusicXML),
and I want to convert that into a form that makes it possible to
ignore ties and see notes as having a single duration.


but can't you just say that the first note of a tie has the indicated 
start time and a duration which is the sum of the tied notes?  i don't 
know musicXML, but i'm not seeing why that would be hard...


That's what I want to do. I'm asking about a good way to write the 
algorithm that traverses the notes and reconstructs the document with the 
correct duration in each note. Actually, I don't want to lose information 
about the original form of the document, so I have separate fields for the 
duration of the graphical single note, and the duration of the tied chain.


Actually, it is better to speak of the end time than the duration, because 
what units do you put duration in? Beats? The time signature could be 
changing measure to measure. MusicXML position? The meaning of one 
position changes measure to measure and can be different in different 
parts. It can get confusing. So I use this concept of location:


data Loc = Loc Int Rational   -- measure number and beat within the measure

I.e. measure 1, beat 2
 measure 7, beat 3 1/2

I use Rational so there is no worry about precision of Floats.

Thanks,
Mike



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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread Michael Mossey



erik flister wrote:


That's what I want to do. I'm asking about a good way to write the
algorithm that traverses the notes and reconstructs the document
with the correct duration in each note. 



why isn't this as simple as 


Erik,
I'm learning from your code examples, but I don't understand how this 
turned into an argument about simplicity. I never said it was complex. I do 
admit it's probably simpler than my initial approach.


Maybe I should take a step back and describe my goals. I am experimenting 
with algorithms for putting a human touch on midi playback. I will use 
Finale to enter the music, then export as MusicXML to my software. Getting 
from MusicXML---which is a complex format that encompasses everything from 
notational subtleties to performance subtleties---into a relatively simple 
internal representation is truly the easy part. The real meat of my project 
is the code to perform the music.



foldr'ing something like this over the xml 
notes (assuming monophony and that they are listed in order of start time)?


In a MusicXML document, you can't assume

  - that the notes are in order of start time
  - monophony
  - that two tied notes are immediately adjacent in the data

None of that is true. I conceive of this problem as multiple passes. On the 
first pass, I translate XML notes into a convenient internal 
representation, on the second pass sort them, then make a pass to figure 
out ties. Whether this is the best approach, I do not know. I am here to learn.


Regarding my use of Rational, it's because I'm representing *notated* 
durations or positions in time, which are always fractions of integers. 
Suppose I give the command to my program to play via midi everything from 
bar 1 beat 1 to bar 2 beat 2 1/2. I want to use Rational so I know 2 1/2 
means 2 1/2 and not 2.499. (*) However, *performed* times are a 
matter of tempo, accel, rit, trills, tremolo, arpeggio etc., and are 
probably best conceived as Real.


I don't quite get this:

 forall x. (Real x, Fractional x) = x if you're picky.

Thanks,
Mike

(*) I may want to use the location of a note (bar and beat) as the key in a 
Map, which I believe should be done with Rational and not Float.


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


Re: [Haskell-cafe] music-related problem

2010-07-04 Thread erik flister

  I don't understand how this turned into an argument about simplicity. I
 never said it was complex.


i wasn't arguing, just confused about what you were asking cuz i didn't see
what wasn't straightforward.  so i addressed the straightforward
interpretation in order to ask what that was missing.  :)  looks like
polyphony is the issue, so i think you need a directed acyclic graph (DAG).

http://hackage.haskell.org/packages/archive/containers/0.3.0.0/doc/html/Data-Graph.html

since every note has at most one pre-Tie and one post-Tie, i guess you don't
need a general DAG -- but a graph library would have the algorithms for
walking the Ties (ie, dfs, components, reachable, etc. in the mentioned
library).

I conceive of this problem as multiple passes. On the first pass, I
 translate XML notes into a convenient internal representation, on the second
 pass sort them, then make a pass to figure out ties. Whether this is the
 best approach, I do not know.


sure that makes sense, i was just addressing the last pass, the matter of
wiring up the tie references.


 Regarding my use of Rational, it's because I'm representing *notated*
 durations or positions in time, which are always fractions of integers.
 Suppose I give the command to my program to play via midi everything from
 bar 1 beat 1 to bar 2 beat 2 1/2. I want to use Rational so I know 2 1/2
 means 2 1/2 and not 2.499.


i wasn't suggesting anything Numeric for durations -- those are NoteDurs
like (Dotted $ Triplet Half).  you don't need numerics until resolving
temporal locations, like milliseconds or subdivisions of a beat.  those may
be irrational numbers (consider if the tempo is irrational, or tiny random
jitter in timing) -- though it's a totally pedantic point on my part and
realistically won't matter.  ;)


 I don't quite get this:

  forall x. (Real x, Fractional x) = x if you're picky.


just being agnostic about the true representation as long as you have
(/), compare, realToFrac,
toRational.  the client can choose some concrete representation like
Rationals, Floats, Doubles, some Fixed resolution, some C type, something
they make up, etc.  space or speed or compatibility may trump precision for
some applications.

(*) I may want to use the location of a note (bar and beat) as the key in a
 Map, which I believe should be done with Rational and not Float.


location needs subdiv, which is (very pedantically) not Rational.  :)

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