[Haskell-beginners] Sequence for functors that are not applicative?
Heinrich Apfelmus
apfelmus at quantentunnel.de
Mon Apr 27 13:34:33 EDT 2009
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
More information about the Beginners
mailing list