Send Beginners mailing list submissions to
        [email protected]

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        [email protected]

You can reach the person managing the list at
        [email protected]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Mapping list over datatype using Traversable     and State
      monad. (Dmitriy Matrosov)
   2. Re:  Mapping list over datatype using Traversable and State
      monad. (Brent Yorgey)


----------------------------------------------------------------------

Message: 1
Date: Mon, 24 Sep 2012 23:15:49 +0400
From: Dmitriy Matrosov <[email protected]>
Subject: [Haskell-beginners] Mapping list over datatype using
        Traversable     and State monad.
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=US-ASCII

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?




------------------------------

Message: 2
Date: Mon, 24 Sep 2012 16:35:45 -0400
From: Brent Yorgey <[email protected]>
Subject: Re: [Haskell-beginners] Mapping list over datatype using
        Traversable and State monad.
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii

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



------------------------------

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 51, Issue 37
*****************************************

Reply via email to