Mapping list over datatype using Traversable and State monad.

Hi. I have a data type data Line a = Line [a] [a] which groups elements into "ordered" (first list) and "other" (second list) ones. And i want a functions representing Line, which actually has two heads (one from 1st list and one from 2nd), as single-headed. In other words, i want to map a list over Line (preserving Line structure), i.e. implement a function with type f :: [a -> b] -> Line a I have done this using Traversable import Data.Monoid import qualified Data.Foldable as F import qualified Data.Traversable as T import Control.Applicative import Control.Monad.State instance Functor Line where fmap f (Line xs ys) = Line (map f xs) (map f ys) instance F.Foldable Line where foldMap f (Line xs ys) = (F.foldMap f xs) `mappend` (F.foldMap f ys) instance T.Traversable Line where traverse f (Line xs ys) = Line <$> (T.traverse f xs) <*> (T.traverse f ys) and my function (which actually used for adding separators (sp ++) into (Line String), and i don't want to add separator before the first element, regardless of whether first element is "ordered" or "other") looks like inlineSeps :: (a -> a) -> Line a -> Line a inlineSeps g = fst . flip runState (id : repeat g) . T.mapM f where f x = do (f : fs) <- get put fs return (f x) It works, but i'm not sure whether using state monad here is good? And whether this is good solution for such problem at all?

On Mon, Sep 24, 2012 at 11:15:49PM +0400, Dmitriy Matrosov wrote:
Hi.
I have a data type
data Line a = Line [a] [a]
which groups elements into "ordered" (first list) and "other" (second list) ones. And i want a functions representing Line, which actually has two heads (one from 1st list and one from 2nd), as single-headed. In other words, i want to map a list over Line (preserving Line structure), i.e. implement a function with type
f :: [a -> b] -> Line a
I have done this using Traversable
import Data.Monoid import qualified Data.Foldable as F import qualified Data.Traversable as T import Control.Applicative import Control.Monad.State
instance Functor Line where fmap f (Line xs ys) = Line (map f xs) (map f ys) instance F.Foldable Line where foldMap f (Line xs ys) = (F.foldMap f xs) `mappend` (F.foldMap f ys) instance T.Traversable Line where traverse f (Line xs ys) = Line <$> (T.traverse f xs) <*> (T.traverse f ys)
and my function (which actually used for adding separators (sp ++) into (Line String), and i don't want to add separator before the first element, regardless of whether first element is "ordered" or "other") looks like
inlineSeps :: (a -> a) -> Line a -> Line a inlineSeps g = fst . flip runState (id : repeat g) . T.mapM f where f x = do (f : fs) <- get put fs return (f x)
It works, but i'm not sure whether using state monad here is good? And whether this is good solution for such problem at all?
This seems reasonable to me. If you tried to implement it "directly" you would end up with awkward special cases for when the first list is empty, and so on; I like how this solution uses Traversable to abstract away from the actual structure of Lines. My one suggestion might be to abstract out the "zippy apply" pattern, like so: zipApp :: Traversable f => [a -> b] -> f a -> f b zipApp fs = fst . flip runState fs . T.mapM f where f x = ... etc, same as above Then inlineSeps g = zipApp (id : repeat g), and you can reuse zipApp for other things. -Brent

On Mon, 24 Sep 2012 16:35:45 -0400
Brent Yorgey
My one suggestion might be to abstract out the "zippy apply" pattern, like so:
zipApp :: Traversable f => [a -> b] -> f a -> f b zipApp fs = fst . flip runState fs . T.mapM f where f x = ... etc, same as above
Then inlineSeps g = zipApp (id : repeat g), and you can reuse zipApp for other things.
Thanks! This is nicer, indeed. Perhaps, the last piece i'm missed for :)

I have one more question. Also i need to zipApp list to part of Line: either to only first list ("ordered" elements) or to only second ("other" elements). I have implemented this using Monoid: import Data.Monoid instance Monoid (Line a) where mempty = Line [] [] (Line xs ys) `mappend` (Line xs' ys') = Line (xs `mappend` xs') (ys `mappend` ys') onlyOrdered :: Line a -> Line a onlyOrdered (Line xs ys) = Line xs [] onlyOthers :: Line a -> Line a onlyOthers (Line xs ys) = Line [] ys and function looks like inlineToOrdered :: (a -> a) -> Line a -> Line a inlineToOrdered g = mappend <$> zipApp (id : repeat g) . onlyOrdered <*> onlyOthers It works as well, but is this solution good? Or there is some better way to limit "scope" of function application to only part of datatype?
participants (2)
-
Brent Yorgey
-
Dmitriy Matrosov