
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