making translation from imperative code

I'm translating a Python program into Haskell, and running into a problem---a type of code where I don't know how to make the conceptual shift. The Python code does a graphical layout of a music score. There is a loop in which it add items (chords, symbols, text, etc.) one at a time, moving to the right, until it reaches the end of the line. So in typical imperative code, we have a bunch of loop state, such as - xpos of last chord or symbol placed - time of last chord or symbol placed - several StaffData objects, each containing the symbols that went on that particular staff - a cache of miscellaneous information about each symbol for later reference So imperative code is pretty simple: loop, and each time update the state. Much of this state consists of lists to which symbols are added once per loop. I'm not sure how to conceive of this problem in Haskell. Without using mutable variables, I would have to "rebuild" the state on each loop. I can do that, but I don't want to see an ugly proliferation of variables. I would like to encapsulate the state in a single object so I can pass it around as a single variable, like LoopState = LoopState { lastXPos :: Int, lastTime :: Double, staffDataLists :: [ ( String, StaffData ) ], chunkCache :: [ ( Double, Chunk ) ] } So lets say I have an instance of this call x. Let's say I want to create y, by "updating" lastXPos. Do I have to do something like this: newLastXPos = 25 y = LoopState ( newLastXPos, lastTime x, staffDataLists x, chunkCache x ) Obviously this is verbose compared to an imperative language in which one would say: newLastPos = 25 x.setLastXPos( newLastXPos ) I am aware that Haskell provides some mutable structures, but part of what drew me to Haskell was the benefit of avoiding mutable data (reducing bugs and making it easier to reason about my program's behavior). Are there any shortcuts for doing things like the above? Thanks, Mike

On Tue, Mar 31, 2009 at 1:54 PM, Michael Mossey
I'm translating a Python program into Haskell, and running into a problem---a type of code where I don't know how to make the conceptual shift.
The Python code does a graphical layout of a music score. There is a loop in which it add items (chords, symbols, text, etc.) one at a time, moving to the right, until it reaches the end of the line. So in typical imperative code, we have a bunch of loop state, such as
- xpos of last chord or symbol placed - time of last chord or symbol placed - several StaffData objects, each containing the symbols that went on that particular staff - a cache of miscellaneous information about each symbol for later reference
So imperative code is pretty simple: loop, and each time update the state. Much of this state consists of lists to which symbols are added once per loop.
I'm not sure how to conceive of this problem in Haskell. Without using mutable variables, I would have to "rebuild" the state on each loop. I can do that, but I don't want to see an ugly proliferation of variables.
I would like to encapsulate the state in a single object so I can pass it around as a single variable, like
LoopState = LoopState { lastXPos :: Int, lastTime :: Double, staffDataLists :: [ ( String, StaffData ) ], chunkCache :: [ ( Double, Chunk ) ] }
So lets say I have an instance of this call x. Let's say I want to create y, by "updating" lastXPos. Do I have to do something like this:
newLastXPos = 25 y = LoopState ( newLastXPos, lastTime x, staffDataLists x, chunkCache x )
Obviously this is verbose compared to an imperative language in which one would say: newLastPos = 25 x.setLastXPos( newLastXPos )
I am aware that Haskell provides some mutable structures, but part of what drew me to Haskell was the benefit of avoiding mutable data (reducing bugs and making it easier to reason about my program's behavior). Are there any shortcuts for doing things like the above?
Have you considered the sort of named updates like the following? data Foo = Foo { i :: Int, j :: Int } deriving (Show) Loading that into ghci you can do things like this: *Foo> let f = Foo 25 25 *Foo> f Foo {i = 25, j = 25} *Foo> f { i = 35 } Foo {i = 35, j = 25} That might be more to your liking. /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus@therning.org http://therning.org/magnus identi.ca|twitter: magthe

Michael Mossey wrote:
I'm translating a Python program into Haskell, and running into a problem---a type of code where I don't know how to make the conceptual shift.
The Python code does a graphical layout of a music score. There is a loop in which it add items (chords, symbols, text, etc.) one at a time, moving to the right, until it reaches the end of the line. So in typical imperative code, we have a bunch of loop state, such as
- xpos of last chord or symbol placed - time of last chord or symbol placed - several StaffData objects, each containing the symbols that went on that particular staff - a cache of miscellaneous information about each symbol for later reference
So imperative code is pretty simple: loop, and each time update the state. Much of this state consists of lists to which symbols are added once per loop.
Can you elaborate on what exactly the algorithm is doing? Does it just emit notes/chords/symbols at given positions or does it also try to arrange them nicely? And most importantly, "where" does it emit them to, i.e. what's the resulting data structure? So far, the problem looks like a basic fold to me. Regards, apfelmus -- http://apfelmus.nfshost.com

Heinrich Apfelmus wrote:
Michael Mossey wrote:
I'm translating a Python program into Haskell, and running into a problem---a type of code where I don't know how to make the conceptual
...
Can you elaborate on what exactly the algorithm is doing? Does it just emit notes/chords/symbols at given positions or does it also try to arrange them nicely? And most importantly, "where" does it emit them to, i.e. what's the resulting data structure?
So far, the problem looks like a basic fold to me.
Here is some Haskell code that explains the problem in more detail. ------------------------------------------------------------- ------------------------------------------------------------- -- layoutSystem -------------------------------------------------------------- -------------------------------------------------------------- -- A "system" in musical typesetting terminology is a -- collection of staves that are all played simultaneously; -- that is, they are aligned in time and space. This is a -- simple layout algorithm that uses the concept of -- "chunk"--- a chunk is a set of events (notes, dynamic -- changes, etc.) that occur on a subset of the staves, and -- occur at the same time and therefore need to be aligned -- vertically. Each item has a width and items must be -- placed so they don't overlap. (There is no attempt to -- align them in an aesthetically pleasing way; they simply -- must not collide.) -- -- We presume that something called a "score" exists, which -- is an object representing the underlying music data, from -- which can be extracted a list of chunks, each -- associated with the time at which it is played. We -- don't show the structure of a score here; we just -- assume that we can operate on a score via two -- functions: -- -- A function to grab a chunk: -- scoreGetChunkData :: Score -> Time -> ChunkData -- A function to get time of next chunk: -- scoreNextTime :: Score -> Time -> Time -- -- This basic structure of this algorithm is a loop with state. -- Here's the state. -- 'time' :: Double -- is the time of next chunk to layout. -- 'staffLayouts' :: [( String, StaffLayout)] -- is an -- association list of staff names and StaffLayout -- objects. Each StaffLayout object accumulates the chunks -- that belong to that staff. -- 'val' :: Int -- This is the next x-position that is -- available for placing a new chunk (this -- is an abbreviation for vertical -- alignment line). -- 'chunkDataMem' This is a cache or memory of all chunks -- we have encountered in this system, for -- lookup later. data SystemLayoutState = SystemLayoutState { time :: Double, staffLayouts :: [ ( String, StaffLayout ) ], val :: Int, chunkDataMem :: [ ChunkData ] } layoutSystem Double -> Score -> Int -> Config -> SystemLayoutState layoutSystem firstTime score rightBorder config = -- Work is done by helper function layoutSystem', -- after giving it the initial state. layoutSystem' initialState -- Construct initial state. where initialState = SystemLayoutState { time = firstTime, staffLayouts = [], val = getConfig config "prefixWidth", storedChunkData = [] } -- Define the helper function layoutSystem' layoutSystem' :: SystemLayoutState -> SystemLayoutState layoutSystem' state = -- Get ChunkData from the score at the time -- associated with the current state. let chunkData = scoreGetChunkData score (time state) -- Call 'incorporateChunkData' to try to add -- it to the score. This will return a -- tuple, the first member being the status -- (True means we can add no more chunks -- because we ran out of horizontal space) -- and the second is updated state. case incorporateChunkData state chunkData rightBorder of ( True, state' ) -> state' ( False, state' ) -> tryAgain state' -- We separate the definition of tryAgain just to make -- the structure of this whole function a little -- clearer. tryAgain asks the score for the next -- time at which a chunk exists. In the case there -- *are no more* chunks, it terminates the -- recursion, while also modifying the state in -- some way to communicate that the recursion -- terminated *because of running out of chunks* -- instead of running out of horizontal -- space. Otherwise it calls back to layoutSystem'. tryAgain state = case scoreNextTime score (time state) of -1 -> indicateNoMoreChunks state t -> layoutSystem' (setTime state t)

Michael Mossey wrote:
Heinrich Apfelmus wrote:
Can you elaborate on what exactly the algorithm is doing? Does it just emit notes/chords/symbols at given positions or does it also try to arrange them nicely? And most importantly, "where" does it emit them to, i.e. what's the resulting data structure?
So far, the problem looks like a basic fold to me.
Here is some Haskell code that explains the problem in more detail. [...]
Thanks for the elaboration. I think the code doesn't separate concerns very well; mixing information about widths and times, page size and the recursion itself into one big gnarl. Also, there is one important issue, namely returning a special value like -1 as error code in
tryAgain state = case scoreNextTime score (time state) of -1 -> indicateNoMoreChunks state t -> layoutSystem' (setTime state t)
Don't do this, use Maybe instead tryAgain state = case scoreNextTime score (time state) of Nothing -> indicateNoMoreChunks state Just t -> layoutSystem' (state { time = t }) where Nothing indicates failure and Just success. Back to the gnarl in general, I still don't have a good grasp on the problem domain, which is key to structuring the algorithm. Therefore, I'll expand on toy model and you tell me how it differs from the real thing. The model is this: we are given several lists of notes (f.i. a piano part and a vocal line) where each note is annotated with the time it is to be played at. We abstract away the fact that we are dealing with musical notes and simply consider a list of *events* type Time = Integer type Events a = [(Time, a)] with the invariant that the timestamps are (strictly) increasing: valid :: Events a -> Bool valid xs = all $ zipWith (\(t1,_) (t2,_) -> t1 < t2) xs (drop 1 xs) Now, the toy task is to merge several lists of similar events into one big list that is ordered by time as well. merge :: [Events a] -> Events [a] Since some events may now occur simultaneously, the events of the results are actually lists of "primitive" events. One possibility for implementing merge is to start with a function to merge two event lists merge2 :: Events [a] -> Events [a] -> Events [a] merge2 [] ys = ys merge2 xs [] = xs merge2 xs@((tx,x):xt) ys@((ty,y):yt) = case compare tx ty of LT -> (tx,x ) : merge2 xt ys EQ -> (tx,x++y) : merge2 xt yt GT -> (ty, y) : merge2 xs yt and to apply it several times merge = foldr merge2 [] . map lift where lift = map $ \(t,x) -> (t,[x]) Another possibility is to simply concatenate everything first and then sort by time merge = map (\((t,x):xs) -> (t,x:map snd xs)) . groupBy ((==) `on` fst) . sortBy (comparing fst) . concat The code above can be made more readable by choosing nice names like time = fst event = snd or avoiding pairs altogether and implementing these names as record fields. Also, the (&&&) combinator from Control.Arrow is very handy. merge = map (time . head &&& map event) . groupBy ((==) `on` time) . sortBy (comparing time) . concat I hope this gives you a few ideas to think about. How does this toy model differ from the real thing? Regards, apfelmus PS: If some parts of my example code give you trouble, it's probably fastest to ask around on the #haskell IRC channel. -- http://apfelmus.nfshost.com

Heinrich Apfelmus wrote:
Michael Mossey wrote:
Heinrich Apfelmus wrote:
Can you elaborate on what exactly the algorithm is doing? Does it just emit notes/chords/symbols at given positions or does it also try to arrange them nicely? And most importantly, "where" does it emit them to, i.e. what's the resulting data structure?
So far, the problem looks like a basic fold to me. Here is some Haskell code that explains the problem in more detail. [...]
Thanks for the elaboration.
I think the code doesn't separate concerns very well; mixing information about widths and times, page size and the recursion itself into one big gnarl.
Also, there is one important issue, namely returning a special value like -1 as error code in
tryAgain state = case scoreNextTime score (time state) of -1 -> indicateNoMoreChunks state t -> layoutSystem' (setTime state t)
Don't do this, use Maybe instead
tryAgain state = case scoreNextTime score (time state) of Nothing -> indicateNoMoreChunks state Just t -> layoutSystem' (state { time = t })
where Nothing indicates failure and Just success.
Okay, tried to give some more detail. thanks for the interesting code. I will study it some more. But here's the original task. {- 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 in 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 sounding item. 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 ( True, state', slayout' ) -> layoutSystem' state' slayout' ( False, 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 item 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 )
participants (3)
-
Heinrich Apfelmus
-
Magnus Therning
-
Michael Mossey