[Haskell-cafe] a problem I can't solve simply

Evan Laforge qdunkan at gmail.com
Mon Dec 14 20:28:39 UTC 2015


You have separate streams of overlapping events, so if you merge them
into one stream your life will be easier:

mergeOn key = Data.List.Ordered.mergeBy (Data.Ord.comparing key)

computeEndMsr begin = findEnd begin . skip . mergeOn fst
  where
  -- drop until the begin measure
  skip = dropWhile ((<begin) . measureOf . fst)
  -- find the first spot where findEmptyMeasures is Just
  findEnd = msum . mapNext findEmptyMeasures

-- map a function that needs to know the future
mapNext f xs = zipWith f xs (drop 1 (List.tails xs))

-- find a 2 measure gap, return measure of end of the last note before it
findEmptyMeasures note (next : _)
  | measureOf (fst next) >= measureOf (snd note) + 2 = Just (measureOf snd note)
  | otherwise = Nothing

You'll need 'measureOf :: Time -> MeasureNumber', which means you can
only have a single global time signature that never changes.

All untested of course, but I think this should have at least some
hints in it.  Data.List.Ordered is from data-ordlist, which is
generally useful.

You also have an unstated precondition, which is that Staff is in time
order, which is useful but a hassle to maintain.  I myself would be
open to advice on how to maintain a ordered invariant :)  In my own
program (which is also for music), I keep an Ordered flag, and map
operations are categorized by whether they maintain or could destroy
the order.  Well, that's the plan at least.

On Mon, Dec 14, 2015 at 2:39 AM, Dennis Raddle <dennis.raddle at gmail.com> wrote:
> I have a problem that doesn't seem hard to state but I can't seem to solve
> without a bunch of complex code.
>
> This relates to my musical score playback. In using it to play music, I
> don't always want to play back the entire source musical document, but
> rather play a range of measures. So I might give a command to my app like
> "play 1-3" which means play measures 1 through 3.
>
> There is a time saving feature, which is that I can type "play 10" which
> means start the playback at measure 10 and continue until the first
> occurrence of two empty measures. This is a common use case.
>
> So I have to write a function that takes a start measure and computes the
> end measure by scanning for two empty measures.
>
> Let's say for simplicity's sake that we'll forget about "measures" and just
> say that notes have a start time and end time, which will be integers.
>
> type Note = (Int,Int)
>
> A musical score can have several individual staves (notes for individual
> instruments), so it will look like this:
>
> type Staff = [Note]
>
> type Score = [Staff]
>
> I need to write a function as follows
>
> computeEndMsr :: Int -> Score -> Int
> computeEndMsr beginMsr score = ...
>
> Some examples:
>
> Here's a score with just one staff, to give you an idea.
>
> score1 = [ [(1,3), (2,4), (7,10)] ]
>
> -- In the following case a two-unit gap is found at units 5 and 6.
> computeEndMsr 1 score1 = 4
>
> computeEndMsr 5 score1 = should throw an error indicating that a gap was
> found immediately and no actual notes were included
>
> -- In the following case, the maximum unit of any note is 10, so that is
> what is computed
> computeEndMsr 6 score1 = 10
>
> -- This case illustrates how it's okay if the computed end measure is equal
> to the begin msr
> computeEndMsr 10 score1 = 10
>
> computeEndMsr 11 score1 = should throw an error indicating that the given
> begin msr is past the end of any note in the score
>
> This example has only one staff, but a score can have multiple staves. Also
> the timing and duration of notes can overlap, either on one staff or across
> multiple staves.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list