[Haskell-beginners] Re: CORRECTED: making translation from imperative code]

Heinrich Apfelmus apfelmus at quantentunnel.de
Thu Apr 2 20:18:39 EDT 2009


Michael Mossey wrote:
> Read this version.
> 
> A composition consists of several voices or instruments, each indicated
> by its own *staff*. Visually, a staff is a layout of items such as
> notes, clef signs, and accidentals arranged horizontally from left to
> right, representing increasing time.
> 
> 
> A *system* is a set of staves stacked vertically that represent
> instruments playing at the same time.
> 
> Here is a simple representation of a system, in which the pipe character
> represents items. Note that some of the items are aligned vertically
> meaning they will play at the same time. At other times, only one
> staff contains a note.
> 
> staff 1:   |    |  | |
> staff 2:     |  |    | |
> 
> Next we elaborate this model to show that items have visual width. Here
> they are represented by clusters of x's with a pipe in the middle. The pipe
> represents the part of the item that needs to be aligned with items on
> other staves. For example, in the visual representation of a chord,
> the part of the chord called the notehead needs to be aligned with
> noteheads on other staves. (A chord includes other symbols, like
> accidentals
> and flags, which get drawn to the right or left of the notehead and don't
> need to be aligned vertically with anything else.)
> 
> 
> staff 1:  x|x xx|xx        x|x
> 
> staff 2:       x|x x|x xxxxx|xxxxx
> 
>            a    b   c       d
> 
> Here you can see that there is an additional constraint on layout,
> which is that items need to have horizontal space around them so they
> don't collide. For instance, the very wide item at 'd' (on staff 2) means
> that the item on staff 1 at 'd' has to be positioned far to the right
> of its previous item.

A nice problem with an elegant solution. Let me demonstrate.

First, let's solve the simpler problem of aligning just a single staff
on unlimited paper. In other words, we are given a list of items that
extend to the left and right, and we want to calculate a position for
each one. In fact, let's dispense with items entirely and just work with
a list of extents directly.

   type Pos   = Integer
   type Width = Pos

   align :: [(Width,Width)] -> [Pos]

For instance, the item  (3,4)  corresponds to

   xxx|xxxx

Implementing this functions is straightforward

   align xs = scanl (+) a gaps
      where
      (a:as,bs) = unzip xs
      gaps      = zipWith (+) bs as

This is a very tight layout without any whitespace, but we can add some
after the fact

   addWhitespace :: Width -> [Pos] -> [Pos]
   addWhitespace margin = zipWith (+) [0,margin..]


With this, we can now align a list of events (from my previous message)
given a function that tells us their visual extents.

   alignStaff :: (a -> (Width,Width)) -> Events a -> [Pos]
   alignStaff f = align . map f


Now, what about the problem of aligning several staves on unlimited
paper? It turns out that we've already solved it! After all, we can
interpret a vertical group of items as a compound item whose total width
is just the maximum width of its components.

   alignStaves :: (a -> (Width,Width)) -> [Events a] -> [Pos]
   alignStaves f = alignStaff f' . merge
      where f' = (maximum *** maximum) . unzip . map f

In other words, we can lay out a group of staves by first merging them
in time order (as done in my previous post) and then treating the result
as a "compound" staff.


> Note that data exists in two domains: there is data that describes notes;
> that is, pitches and timbres and volumes and times and duration. We'll
> call this the 'score'. It's the fundamental data. Then there is the
> visual *representation* of the score. Here we are concerned only with
> creating a visual representation. However, we need to refer to
> data in the score.

Thanks to polymorphism, keeping this data around is no problem. The
alignStaves  function simply doesn't care what items it is going to
align, it only wants to know their widths. In fact, making  alignStave
polymorphic is key to reusing it for groups of staves.

In other words, polymorphism is key to separating concerns. You should
structure your layout engine as some kind of library that can align
anything, caring only about widths and heights. For instance, dealing
with finite paper size can be packed neatly into the  align  function.


Regards,
apfelmus

--
http://apfelmus.nfshost.com



More information about the Beginners mailing list