
This is probably a side-effect of coming from OO land, but I'm confused about how to organize my data. Let's say I want to model musical information that occurs on a single staff. A staff consists of a list of StaffItem which occurs at specific times. type Time = Double type Staff = [(Time,StaffItem)] A StaffItem can be one of several things. Let's say it can be a "chord" or a "control". I might like to define Chord and Control first: data Chord = Chord { duration :: Double, notes :: [Note] } data Control = DynamicMark Int | TempoMark Int Okay, so now I want to express the idea a StaffItem can be a Chord or a Control. data StaffItem = StaffItemChord Chord | StaffItemControl Control My problem is the awkward need for separately named constructors "StaffItemChord" and "StaffItemControl". Is there a better way? (Is this even right?) Thanks, Mike

Some additional thoughts: Here is something I'm struggling with. Let's say a piece of music is several staves filled with chords. Staves have names. Each chord in a staff has a time. In informal notation: staff "fred": (time 1.0, chord 1), (time 1.5, chord 2), (time 2.0, chord 3) staff "bob" : (time 1.0, chord 4), (time 2.0, chord 5) When laying out music, I need to find "verticals", which are chords located on different staves which happen to coincide in time. For instance, the above has three verticals: time 1.0: ("fred", chord 1), ("bob", chord 4) time 1.5: ("fred", chord 2) time 2.0: ("fred", chord 3), ("bob", chord 5) I want to write a function that converts the first way of organizing the information into the second. I tried writing types like type Chord = ... type Time = Double type Name = String type TimedChord = (Time,Chord) type Staff = [(Time,Chord)] type NamedStaff = (Name,Staff) type NamedChord = (Name,Chord) type Vertical = [NamedChord] type TimedVertical = (Time,Vertical) The function I want is convert :: [NamedStaff] -> [TimedVertical] As you can imagine, this is a confusing mess, with all these variants on named and timed things. I thought it might help to create functors called Named and Timed, which might help abstracting operations on named and timed things. For example, datatype Named a = Named { namedName :: Name, namedData :: a } instance Functor Named = name a :: Name name a = namedName a x `fmap` f = Named { namedName = namedName x, namedData = f $ namedData x } Any other suggestions? Thanks, Mike

Am Montag 20 April 2009 02:10:42 schrieb Michael Mossey:
Some additional thoughts:
Here is something I'm struggling with. Let's say a piece of music is several staves filled with chords. Staves have names. Each chord in a staff has a time.
In informal notation:
staff "fred": (time 1.0, chord 1), (time 1.5, chord 2), (time 2.0, chord 3) staff "bob" : (time 1.0, chord 4), (time 2.0, chord 5)
When laying out music, I need to find "verticals", which are chords located on different staves which happen to coincide in time. For instance, the above has three verticals:
time 1.0: ("fred", chord 1), ("bob", chord 4) time 1.5: ("fred", chord 2) time 2.0: ("fred", chord 3), ("bob", chord 5)
I want to write a function that converts the first way of organizing the information into the second. I tried writing types like
type Chord = ... type Time = Double type Name = String
type TimedChord = (Time,Chord) type Staff = [(Time,Chord)] type NamedStaff = (Name,Staff) type NamedChord = (Name,Chord) type Vertical = [NamedChord] type TimedVertical = (Time,Vertical)
The function I want is
convert :: [NamedStaff] -> [TimedVertical]
What about import Data.Function (on) import Data.List convert namedStaffs = map timeVertical verticals where nameTimedChords (name,tcs) = [(time,name,chord) | (time, chord) <- tcs] timedNamedChords = sort . foldr merge [] . map nameTimedChords $ namedStaffs fst3 (x,_,_) = x verticals = groupBy ((==) `on` fst3) timedNamedChords timeVertical v@((t,_,_):_) = (t,[(name,chord) | (_,name,chord) <- v]) ?
As you can imagine, this is a confusing mess, with all these variants on named and timed things. I thought it might help to create functors called Named and Timed, which might help abstracting operations on named and timed things. For example,
datatype Named a = Named { namedName :: Name, namedData :: a }
instance Functor Named = name a :: Name name a = namedName a x `fmap` f = Named { namedName = namedName x, namedData = f $ namedData x }
Any other suggestions? Thanks, Mike

Daniel Fischer wrote:
import Data.Function (on) import Data.List
convert namedStaffs = map timeVertical verticals where nameTimedChords (name,tcs) = [(time,name,chord) | (time, chord) <- tcs] timedNamedChords = sort . foldr merge [] . map nameTimedChords $ namedStaffs fst3 (x,_,_) = x verticals = groupBy ((==) `on` fst3) timedNamedChords timeVertical v@((t,_,_):_) = (t,[(name,chord) | (_,name,chord) <- v])
?
Hi Daniel, Thanks, that is nice and I will learn a lot by studying it. However, a problem. It will be a big benefit to do this lazily because I only need to extract as many verticals as necessary to fit on one page of layout. I realized, as you did, that it would simplify things to care only about NamedTimedChords: type NamedTimedChord = (Name,Time,Chord) Even though there is some redundancy to have every entry carry along its name and time, it is worth it for simplifying things. Here's what I have, to do this lazily and now caring only about NamedTimedChords: toVerticals :: [[NamedTimedChord]] -> [[NamedTimedChord]] toVerticals [] = [] toVerticals staves = firstVertical : toVerticals remainder where time3 (_,time,_) = time firstVertT = minimum $ map (time3 . head) staves usingStaves = [ s | s <- staves, time3 (head s) == firstVertT ] notUsingStaves = [ s | s <- staves, time3 (head s) /= firstVertT ] firstVertical = map head usingStaves remainder = leftOfUsing ++ notUsingStaves leftOfUsing = filter (not . null) (map tail usingStaves)

Michael Mossey wrote:
toVerticals :: [[NamedTimedChord]] -> [[NamedTimedChord]] toVerticals [] = [] toVerticals staves = firstVertical : toVerticals remainder where time3 (_,time,_) = time firstVertT = minimum $ map (time3 . head) staves usingStaves = [ s | s <- staves, time3 (head s) == firstVertT ] notUsingStaves = [ s | s <- staves, time3 (head s) /= firstVertT ]
realized I could use Data.List.partition for this
firstVertical = map head usingStaves remainder = leftOfUsing ++ notUsingStaves leftOfUsing = filter (not . null) (map tail usingStaves) _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Michael Mossey wrote:
I want to write a function that converts the first way of organizing the information into the second. I tried writing types like
type Chord = ... type Time = Double type Name = String
type TimedChord = (Time,Chord) type Staff = [(Time,Chord)] type NamedStaff = (Name,Staff) type NamedChord = (Name,Chord) type Vertical = [NamedChord] type TimedVertical = (Time,Vertical)
The function I want is
convert :: [NamedStaff] -> [TimedVertical]
As you can imagine, this is a confusing mess, with all these variants on named and timed things. I thought it might help to create functors called Named and Timed, which might help abstracting operations on named and timed things. For example,
datatype Named a = Named { namedName :: Name, namedData :: a }
instance Functor Named = name a :: Name name a = namedName a x `fmap` f = Named { namedName = namedName x, namedData = f $ namedData x }
Any other suggestions?
Functors sounds good to me. data Named a = N Name a data Timed a = T Time a instance Functor Named where ... instance Functor Timed where ... convert :: Named [Timed Chord] -> Timed [Named Chord] Bu you can also use plain type synonyms type Named a = (Name,a) type Timed a = (Time,a) and write your own record selectors by hand name :: Named a -> Name name = fst time :: Timed a -> Time time = fst value :: (b,a) -> a value = snd Regards, apfelmus -- http://apfelmus.nfshost.com

Maybe just bikeshedding here (and on -beginners, no less), but this seems like a job for Data.Traversable.sequence? sequence :: Monad m => t (m a) -> m (t a) Cheers, S. On Apr 20, 2009, at 3:00 AM, Heinrich Apfelmus wrote:
Functors sounds good to me.
data Named a = N Name a data Timed a = T Time a
instance Functor Named where ... instance Functor Timed where ...
convert :: Named [Timed Chord] -> Timed [Named Chord]
Bu you can also use plain type synonyms
type Named a = (Name,a) type Timed a = (Time,a)
and write your own record selectors by hand
name :: Named a -> Name name = fst
time :: Timed a -> Time time = fst
value :: (b,a) -> a value = snd
Regards, apfelmus
-- http://apfelmus.nfshost.com
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Sterling Clover wrote:
Maybe just bikeshedding here (and on -beginners, no less), but this seems like a job for Data.Traversable.sequence?
sequence :: Monad m => t (m a) -> m (t a)
Cheers, S.
Heinrich Apfelmus wrote:
convert :: Named [Timed Chord] -> Timed [Named Chord]
Great idea! My type signature is wrong, it should actually read convert :: [Named [Timed Chord]] -> [Timed [Named Chord]] I'm not sure whether sequence applies directly, type EventList a = [Timed a] is not a monad. It's not quite an applicative functor either, because in (<*>) :: EventList (a -> b) -> EventList a -> EventList b it's not clear what should happen to events from the left and right list that are not simultaneous. This needs further thought. Regards, apfelmus -- http://apfelmus.nfshost.com

Hello, I would like to write a function convert :: [(Name, [(Time, Chord)])] -> [(Time, [(Name, Chord)])] which transposes a finite map [(Name,b)] of event lists [(Time,a)] into an event list of finite maps. Sterling remarked that this looks very much like a job for sequence , but since event lists are not even applicative functors, I wonder whether an abstraction with less requirements can be found. Below is a first try. Heinrich Apfelmus wrote:
Sterling Clover wrote:
Maybe just bikeshedding here (and on -beginners, no less), but this seems like a job for Data.Traversable.sequence?
sequence :: Monad m => t (m a) -> m (t a)
Great idea!
My type signature is wrong, it should actually read
convert :: [Named [Timed Chord]] -> [Timed [Named Chord]]
I'm not sure whether sequence applies directly,
type EventList a = [Timed a]
is not a monad. It's not quite an applicative functor either, because in
(<*>) :: EventList (a -> b) -> EventList a -> EventList b
it's not clear what should happen to events from the left and right list that are not simultaneous. This needs further thought.
It appears that type EventList a = [(Time, a)] -- ascending times is not an applicative functor, but only a "monoid preserving functor" instance Monoid a => Monoid (EventList a) where mempty = [] mappend xs ys = map mconcat . groupBy ((==) `on` fst) . sortBy (comparing fst) (xs ++ ys) The same is true for type Group a = [(Name, a)] instance Monoid a => Monoid (Group a) where ... Put differently, we have two functions unionWith :: (a -> a -> a) -> EventList a -> EventList a -> EventList a unionWith :: (a -> a -> a) -> Group a -> Group a -> Group a Additionally, we need concat :: (a -> a -> a) -> Group a -> a and a strange function cobind' :: Functor f => Group (f a) -> Group (f (Group a)) cobind' xs = [(name, fmap (\y -> (name,y)) x) | (name,x) <- xs] that is reminiscent of a comonad. With this machinery, we can write convert :: Group (EventList a) -> EventList (Group a) convert = concat (unionWith (unionWith snd)) . cobind' No idea whether all this is overkill. After all, convert is but a glorified transpose. Regards, apfelmus -- http://apfelmus.nfshost.com

Michael Mossey wrote:
I want to write a function that converts the first way of organizing the information into the second. I tried writing types like
type Chord = ... type Time = Double type Name = String
type TimedChord = (Time,Chord) type Staff = [(Time,Chord)] type NamedStaff = (Name,Staff) type NamedChord = (Name,Chord) type Vertical = [NamedChord] type TimedVertical = (Time,Vertical)
The function I want is
convert :: [NamedStaff] -> [TimedVertical]
As you can imagine, this is a confusing mess, with all these variants on named and timed things. I thought it might help to create functors called Named and Timed, which might help abstracting operations on named and timed things. For example,
datatype Named a = Named { namedName :: Name, namedData :: a }
instance Functor Named = name a :: Name name a = namedName a x `fmap` f = Named { namedName = namedName x, namedData = f $ namedData x }
Any other suggestions?
Functors sounds good to me. data Named a = N Name a data Timed a = T Time a instance Functor Named where ... instance Functor Timed where ... convert :: Named [Timed Chord] -> Timed [Named Chord] But you can also use plain type synonyms type Named a = (Name,a) type Timed a = (Time,a) and write your own record selectors by hand name :: Named a -> Name name = fst time :: Timed a -> Time time = fst value :: (b,a) -> a value = snd Regards, apfelmus -- http://apfelmus.nfshost.com

Michael Mossey wrote:
A StaffItem can be one of several things. Let's say it can be a "chord" or a "control". I might like to define Chord and Control first:
data Chord = Chord { duration :: Double, notes :: [Note] } data Control = DynamicMark Int | TempoMark Int
Okay, so now I want to express the idea a StaffItem can be a Chord or a Control.
data StaffItem = StaffItemChord Chord | StaffItemControl Control
My problem is the awkward need for separately named constructors "StaffItemChord" and "StaffItemControl". Is there a better way? (Is this even right?)
Why not simply data StaffItem = Chord { duration :: Double, notes :: [Note] } | DynamicMark Int | TempoMark Int Unless you use Control and Chords in isolation, that's entirely fine. It's basically a question of how much type safety you want. If you have a function like chordName :: Chord -> String that should only with proper Chords and not Control messages, giving it the type signature chordName :: StaffItem -> String is less safe; the compiler won't complain if you pass it a Control message. If you want the compiler to complain, then building "type towers" as you did is the way to go. You can use predefined building blocks like Either type StaffLabel = Either Chord Control to build your types. There are a few methods for making things less clumsy available, like for example Wouter Swierstra. Data types à la carte. http://www.cse.chalmers.se/~wouter/Publications/DataTypesALaCarte.pdf Regards, apfelmus -- http://apfelmus.nfshost.com
participants (4)
-
Daniel Fischer
-
Heinrich Apfelmus
-
Michael Mossey
-
Sterling Clover