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

Michael Mossey mpm at alumni.caltech.edu
Wed Apr 1 02:33:27 EDT 2009



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)


More information about the Beginners mailing list