CORRECTED: making translation from imperative code]

STOP THE PRESSES--- I noticed some goofs (more late-night programming... ) Corrected below. 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. 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. -} -- LayoutItem is a visual representation of a note. The center of the note -- or chord (specifically the part that needs to be aligned vertically) -- goes at position 'pos', the other variables describe how much the -- note sticks out to the left, right, top, and bottom. We omit other -- details about the note. data LayoutItem = LayoutItem { pos :: ( Int, Int ), leftWidth, rightWidth, topHeight, bottomHeight :: Int, staffId :: String } -- ChunkData is 'score' domain data. It represents all notes that start -- sounding at the same time. It is an association list of staff -- names to notes. Note that a complete score is essentially a list of -- chunks in time order. data ChunkData = ChunkData [ ( String, [ Note ] ) ] -- We'll just say a note is an int giving its pitch. type Note = Int -- A system layout is a set of *staves*. Here, staves are -- lists of LayoutItem, put into an association list by staff name. -- There is also a need to make a memo of chunks for future reference. data SystemLayout = SystemLayout { staves :: [ ( String, [ LayoutItem ] ) ], chunkMemo :: [ ChunkData ] } -- This is the loop state. During the loop, 'time' keeps advancing to -- the time of the next chunk, and 'nextX' keeps advancing to the next -- vetical alignment location. data LoopState = LoopState { time :: Double, nextX :: Int } --- Details of score omitted, but assume it has two key functions. data Score = Score ... scoreGetChunkData :: Score -> Time -> ChunkData scoreNextTime :: Score -> Time -> Maybe Time -- layoutSystem works as follows: it takes a time to start the layout -- at, a score, and a maximum paper width, and returns a tuple with the -- LoopState and SystemLayout at termination. -- -- The looping happens in the helper function layoutSystem' which -- has a simple signature: basically all relevant state goes in, -- and all relevant state comes out. (See signtaure below.) -- -- incororateChunkData does the main work of looking at all notes -- in the next chunk and either finguring out how to add them to -- the staves, or indicating they can't be added without going off -- the right edge of the paper. It returns -- a tuple ( Bool, LoopState, SystemLayout ) where the Bool indicates -- success or failure. layoutSystem Time -> Score -> Int -> ( LoopState, SystemLayout ) layoutSystem firstTime score maxWidth = layoutSystem' initialState initialSystemLayout where initialState = LoopState { time = firstTime, nextX = 0 } initialSystemLayout SystemLayout { staves = [], chunkMem = [] } ) layoutSystem' :: LoopState -> SystemLayout ->( LoopState, SystemLayout ) layoutSystem' state slayout = let chunkData = scoreGetChunkData score (time state) in case incorporateChunkData chunkData state slayout maxWidth of ( False, state', slayout' ) -> ( state, slayout ) ( True, state', slayout') -> case scoreNextTime score (time state') of Just t -> layoutSystem' state' { time = t } slayout' Nothing -> ( state', slayout' ) -- incorporateChunkData is a function that does the work of looking at -- all notes -- in the next chunk and either figuring out how to add them to -- the staves, or indicating they can't be added without going off -- the right edge of the paper. It returns -- a tuple ( Bool, LoopState, SystemLayout ) where the Bool indicates -- success or failure. incorporateChunkData :: LoopState -> SystemLayout -> Int -> ( Bool, LoopState, SystemLayout ) incorporateChunkData chunkData state slayout maxWidth = let items = makeLayoutItems chunkData -- Find new x alignment value, which done by finding how far right -- each item needs to go to avoid collision with previous items. -- For each staff 'staffId' and each item 'i' that needs to be added to -- the staff, the question is: how far right does the staff extend, -- and how far left does the new item stick out from its central -- position? That tells you where the new central position needs to go. -- (the function rightExtent finds how far right a staff extends), -- This process needs to be repeated for all staves, noting the -- needed alignment point for each---and then the final determination -- is the maximum of all those alignment points. alignX = max (map (\i -> let r = rightExtent slayout (staffId i) in r + leftWidth i) items) -- Now see if we've run off the right edge of the paper. -- Then check how far to the right each item will extend and -- compare to maxWidth farRight = max ( map (\i -> alignX + rightWidth i) items) if farRight < maxWidth then let slayout' = addItems slayout items alignX state' = state { nextX = alignX + 1 } in ( True, state', slayout' ) else ( False, state, slayout ) _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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

Heinrich Apfelmus wrote:
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.
Hi Heinrich, Okay, I read all of your email, and there is one problem. My layout problem is more complex than I communicated at first. Let me give a more detailed example: staff 1: xxxx|xxxx x|x staff 2: x|xx xxxx|xx staff 3: x|x a b c There are two additional concerns to what you coded up. Notice that parts of events on different staves are allowed to overlap. To determine the spacing from a to b, one has to know the widths of items on each staff to see that they they can be placed with some overlap but won't collide. They can't be treated strictly as a compound item and "going blind" to the parts that make them up. Secondly, look at the item on staff 3 at c. It has no prior item to avoid colliding with, and no items on other staves to line up with, but there is still a constraint on its position: c > b (by some amount that can be experimented with). Here is something I coded up, but didn't test much (other than it compiles): -- Item is a pair giving left width and right width. -- Chunk represents items that must align. There may not be one on every staff, -- hence the use of Maybe type Item = (Int, Int) type Chunk = [ Maybe Item ] -- layout3, given a list of Chunks, will produce a list of integer positions where -- they should be placed. layout3 :: [ Chunk ] -> [ Int ] layout3 cs = layout3' cs (replicate (length cs) 0) -- helper function layout3' takes list of chunks, integer list of "right extents" -- (how far to the right each staff extends at that time), and minimum position -- (which is, in this case, always 1 greater than prior placement position) layout3' :: [ Chunk ] -> [ Int ] -> Int -> [ Int ] layout3' [] _ _ = [] layout3' (c:cs) rs minP = p : layout3' cs rs' (p + 1) where p = maximum $ minP : (map place (zip c rs)) rs' = map advance (zip c rs) place (item, r) = case item of Just ( left, right ) -> r + left _ -> 0 advance (item, p ) = case item of Just ( left, right ) -> p + right _ -> p The near identical functions place and advance really need to be merged. Thanks, Mike

Michael Mossey wrote:
Okay, I read all of your email, and there is one problem. My layout problem is more complex than I communicated at first. Let me give a more detailed example:
staff 1: xxxx|xxxx x|x staff 2: x|xx xxxx|xx staff 3: x|x a b c
There are two additional concerns to what you coded up. Notice that parts of events on different staves are allowed to overlap. To determine the spacing from a to b, one has to know the widths of items on each staff to see that they they can be placed with some overlap but won't collide. They can't be treated strictly as a compound item and "going blind" to the parts that make them up.
Secondly, look at the item on staff 3 at c. It has no prior item to avoid colliding with, and no items on other staves to line up with, but there is still a constraint on its position: c > b (by some amount that can be experimented with).
No problem. :) Reading your code, I'd generally recommend a higher-level approach focusing on *abstraction*. Primitive recursion can do the job, but it's error-prone and tedious and best avoided.
-- Item is a pair giving left width and right width. type Item = (Int, Int) -- Chunk represents items that must align. -- There may not be one on every staff, -- hence the use of Maybe type Chunk = [ Maybe Item ]
Abstraction starts with using type synonyms like type Pos = Int type Width = Pos that indicate what the parameter denotes, not how it's represented by the computer. [Int] is less descriptive than [Pos] (a list of absolute coordinates), because it could also mean [Width] (a list of relative coordinates). For instance, it's possible to add two widths, but adding two positions should be a type error, you may only advance a position by a width. Also, I think that Chunk is too generic a name, but I don't have a good replacement for now. But see below. Abstraction is also key to solving the new problem description with the same algorithm as the old one. In particular, our goal is to implement the function align just like the old one. The core abstraction is that of an *extent*. It's simply a list of widths type Extent = [Width] representing a vertical group of bars. xxxx| |xxxx xx| or |xx = [4,2,3] xxx| |xxx We don't specify whether they are ragged to the right or left. The define the width of an extent to be the maximum width of its bars width :: Extent -> Width width = maximum A Chunk is of course just a pair of extents, one to the left and one to the right extents :: Chunk -> (Extent,Extent) extents = unzip . map (maybe (0,0) id) Now, align is structured just like before, calculating the gaps between different items align :: [(Extent, Extent)] -> [Pos] align xs = scanl (+) (width l) gaps where (l:ls, rs) = unzip xs gaps = zipWith fit rs ls However, extents are now fitted together with fit :: Extent -> Extent -> Width fit xs ys = (+1) . maximum . zipWith (+) xs ys The previous code can be interpreted as fitting extents together with fit xs ys = maximum xs + maximum ys Different definitions of fit yield different layouts algorithms. I'm not happy with the definition of align yet, because the specifics of laying out extents are present in two places, namely width and fit instead of just one, namely fit . This can be remedied by noting that the purpose of width is to fit the first extent to the *left boundary*. In other words, width = fit (repeat 0) (assuming that fit is able to crop and infinite list of widths to the proper size). Thus, we have align xs = scanl1 (+) gaps where (ls,rs) = unzip xs boundary = repeat 0 gaps = zipWith fit (boundary:rs) ls In the end, both align and your layout3 functions do exactly the same calculations, of course, but by virtue of abstraction, the correctness and structure of the former is self-evident.
layout3 :: [ Chunk ] -> [ Int ] layout3 cs = layout3' cs (replicate (length cs) 0) 0
layout3' :: [ Chunk ] -> [ Int ] -> Int -> [ Int ] layout3' [] _ _ = [] layout3' (c:cs) rs minP = p : layout3' cs rs' (p + 1) where p = maximum $ minP : (map place (zip c rs)) rs' = map (advance p) c place (item, r) = case item of Just ( left, right ) -> r + left + 1 _ -> 0 advance p item = case item of Just ( left, right ) -> p + right + 1 _ -> p
Two remarks on the code for pretty printing:
drawLayout :: [ Chunk ] -> [ Int ] -> String drawLayout cs pos = unlines $ makeLines cs pos where
makeLines :: [ Chunk ] -> [ Int ] -> [ String ] makeLines cs@(cs1:_) pos | null cs1 = [] | otherwise = makeLine (map head cs) pos : makeLines (map tail cs) pos
This is basically a function known as transpose (from Data.List). Also, let's reorder the parameters. makeLines :: [Pos] -> [Chunk] -> [String] makeLines pos = map (makeLine pos) . transpose
makeLine :: [ Maybe Item ] -> [ Int ] -> String makeLine items pos = foldl addItem [] (zip items pos)
addItem :: String -> ( Maybe Item, Int ) -> String addItem s ( item, p ) = let le = length s in case item of Just ( l, r ) -> s ++ (replicate (p - le - l) ' ') ++ (replicate l 'x') ++ "|" ++ (replicate r 'x') _ -> s
data1 = [ [ Just (2,2), Just(1,1), Just (2,3 ) ], [ Just (1,1), Just (3,4), Just(1,1) ], [ Just (4,4), Nothing, Just (1,1) ] ]
answer = drawLayout data1 (layout3 data1) main = do putStr answer
main = putStr answer -- no do required
*Main> main xx|xx x|x xxxx|xxxx x|x xxx|xxxx xx|xxx x|x x|x *Main>
Regards, apfelmus -- http://apfelmus.nfshost.com
participants (2)
-
Heinrich Apfelmus
-
Michael Mossey