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

Michael Mossey mpm at alumni.caltech.edu
Thu Apr 2 03:57:20 EDT 2009


Thanks very much for the help... I will look at this over the next couple of 
days. Your code actually addresses a different problem, the one of merging 
separates lists of timed events. I do need to write code to do that eventually, 
so I will try to understand what you have written here. However, the original 
problem concerns visual layout, which actually takes place *after* creating a 
merged list. In layout, items do have times associated with them, but also take 
up physical space. Different items takes up different amounts of space, and at 
any given "time," there may be items on all the staves or  just some of them. I 
will try to come up with

(1) a more succinct explanation of the problem (with textual graphics as a 
visual aid)

(2) a more succinct algorithm.

For example, you are right that I'm mixing concerns. The system layout can 
terminate for two reasons: (1) reached the end of the score (2) reached the 
right edge of the page. There might be a way to simplify the loop or fold so 
that these concerns look more unified.

-Mike

PS a question below:

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.
> 
> 
> 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
> 
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


More information about the Haskell-Cafe mailing list