[Haskell-cafe] foreach

Henning Thielemann lemming at henning-thielemann.de
Wed Sep 13 05:12:35 EDT 2006


On Wed, 13 Sep 2006, Donald Bruce Stewart wrote:

> lemmih:
> > On 9/13/06, Tim Newsham <newsham at lava.net> wrote:
> > >I was rewriting some non-haskell code in haskell and came up with this
> > >construct:
> > >
> > >   foreach l f = mapM_ f l
> > >
> > >   main = do
> > >       args <- getArgs
> > >       foreach args (\arg -> do
> > >           foreach [1..3] (\n -> do
> > >               putStrLn ((show n) ++ ") " ++ arg)
> > >            )
> > >        )
> > >
> > >which is reminiscent of foreach in other languages.  Seems fairly
> > >useful and I was wondering how hard it would be to add some syntactic
> > >sugar to the "do" construct to make it a little prettier (ie.
> > >not require the parenthesis, binding and nested do, as:
> > >
> > >   main = do
> > >       args <- getArgs
> > >       foreach args arg
> > >           foreach [1..3] n
> > >               putStrLn ((show n) ++ ") " ++ arg)
> > >
> > >would this type of transformation be possible with template haskell
> > >or does this need stronger support from the parser to pull off?
> > 
> > How about:
> > 
> >  main = do
> >    args <- getArgs
> >    flip mapM_ args $ \arg ->
> >      flip mapM_ [1..3] $ \n ->
> >        putStrLn $ show n ++ ") " ++ arg
> > 
> 
> Which is, with current Control.Monad:
> 
>    main = do
>      args <- getArgs
>      forM_ args $ \arg ->
>        forM_ [1..3] $ \n ->
>          putStrLn $ show n ++ ") " ++ arg
> 
> I think Tim is looking for an if-then-else "real syntax" feel to his
> `foreach' though. I.e. TH or some small preprocessor.

Adding sugar or using Template Haskell for such a simple task is a bit
unreasonable. I think Tim should use mapM a little bit and then he will
probably need no longer a special syntax.


If you want more sugar, what about the list monad?

main = do
         args <- getArgs
         sequence_ $
           do arg <- args
              n <- [1..3]
              return (putStrLn $ show n ++ ") " ++ arg)

or

main = do
         args <- getArgs
         sequence_ $
           liftM2 (\arg n -> putStrLn $ show n ++ ") " ++ arg)
                  args [1..3]


More information about the Haskell-Cafe mailing list