
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? Tim Newsham http://www.thenewsh.com/~newsham/

On 9/13/06, Tim Newsham
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 -- Cheers, Lemmih

lemmih:
On 9/13/06, Tim Newsham
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. -- Don

On Wed, 13 Sep 2006, Donald Bruce Stewart wrote:
lemmih:
On 9/13/06, Tim Newsham
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]

Hello Henning, Wednesday, September 13, 2006, 1:12:35 PM, you wrote:
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.
i disagree. lack of good syntax makes imperative programming in Haskell less convenient. i want to have such syntax in order to make Haskell great imperative language: sum <- new 0 arr <- new Array[1..3] for i in [1..3] do sum += i arr[i] := sum for i in [1..3] while arr[i]<2 do print arr[i] it will be even better to have ability to define such syntax constructs in user program -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Wed, 13 Sep 2006, Bulat Ziganshin wrote:
Wednesday, September 13, 2006, 1:12:35 PM, you wrote:
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.
i disagree. lack of good syntax makes imperative programming in Haskell less convenient. i want to have such syntax in order to make Haskell great imperative language:
sum <- new 0 arr <- new Array[1..3] for i in [1..3] do sum += i arr[i] := sum for i in [1..3] while arr[i]<2 do print arr[i]
let arr = scanl1 (+) [1..3] in mapM_ print (takeWhile (<2) arr)

On 9/13/06, Henning Thielemann
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, what about using ListT to combine it with IO, eliminating the need for two separate `do' blocks? main = (>> return ()) $ runListT $ do arg <- ListT getArgs n <- ListT $ return [1..3] liftIO $ putStrLn ((show n) ++ ") " ++ arg) Mike

Hello Michael, Thursday, September 14, 2006, 12:44:37 AM, you wrote:
Or, what about using ListT to combine it with IO, eliminating the need for two separate `do' blocks?
according to my experience, in most cases we need two do blocks just because outer one contains more code after inner one finishes up -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Lemmih wrote:
main = do args <- getArgs flip mapM_ args $ \arg -> flip mapM_ [1..3] $ \n -> putStrLn $ show n ++ ") " ++ arg
Or even: main = do args <- getArgs putStr $ unlines [ show n ++ ") " ++ arg | arg <- args, n <- [1..3] ] I'm really at a loss trying to understand why some people seem to like the imperative style. In fact, most of the time, the strings in the code above are better replaced by Doc from Text.PrettyPrint. Udo. -- Worrying is like rocking in a rocking chair -- It gives you something to do, but it doesn't get you anywhere.

Hello Udo, Wednesday, September 13, 2006, 12:53:38 PM, you wrote:
main = do args <- getArgs flip mapM_ args $ \arg -> flip mapM_ [1..3] $ \n -> putStrLn $ show n ++ ") " ++ arg
Or even:
main = do args <- getArgs putStr $ unlines [ show n ++ ") " ++ arg | arg <- args, n <- [1..3] ]
I'm really at a loss trying to understand why some people seem to like the imperative style. In fact, most of the time, the strings in the code above are better replaced by Doc from Text.PrettyPrint.
because REAL code is somewhat larger than examples. try to rewrite the following: directory_blocks <- (`mapM` splitBy (opt_group_dir command) files_to_archive) ( \filesInOneDirectory -> do datablocks <- (`mapM` splitToSolidBlocks filesInOneDirectory) ( \filesInOneDataBlock -> do let compressor = map (freearcLimitDictionary$ clipToMaxInt totalBytes) (data_compressor filesInOneDataBlock) totalBytes = sum$ map (fiSize.cfFileInfo) filesInOneDataBlock copy_solid_block = isWholeSolidBlock filesInOneDataBlock writeBlock pipe DATA_BLOCK compressor copy_solid_block $ do dir <- if copy_solid_block then do sendP pipe (CopySolidBlock filesInOneDataBlock) return$ map fileWithCRC filesInOneDataBlock else if (compressor==[aFAKE_COMPRESSION]) then do sendP pipe (FakeFiles filesInOneDataBlock) return$ map (FileWithCRC 0 . cfFileInfo) filesInOneDataBlock else do mapMaybeM (read_file command bufOps decompress_pipe) filesInOneDataBlock processDir dir return dir ) blocks_info <- replicateM (length datablocks) (getP backdoor) arcpos <- archiveGetPos archive writeControlBlock DIR_BLOCK dir_compressor $ do archiveWriteDir blocks_info arcpos receiveBuf sendBuf ) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

At Wed, 13 Sep 2006 15:24:39 +0400, Bulat Ziganshin wrote:
because REAL code is somewhat larger than examples. try to rewrite the following:
directory_blocks <- (`mapM` splitBy (opt_group_dir command) files_to_archive) ( \filesInOneDirectory -> do datablocks <- (`mapM` splitToSolidBlocks filesInOneDirectory) ( \filesInOneDataBlock -> do let compressor = map (freearcLimitDictionary$ clipToMaxInt totalBytes) (data_compressor filesInOneDataBlock) totalBytes = sum$ map (fiSize.cfFileInfo) filesInOneDataBlock copy_solid_block = isWholeSolidBlock filesInOneDataBlock writeBlock pipe DATA_BLOCK compressor copy_solid_block $ do dir <- if copy_solid_block then do sendP pipe (CopySolidBlock filesInOneDataBlock) return$ map fileWithCRC filesInOneDataBlock else if (compressor==[aFAKE_COMPRESSION]) then do sendP pipe (FakeFiles filesInOneDataBlock) return$ map (FileWithCRC 0 . cfFileInfo) filesInOneDataBlock else do mapMaybeM (read_file command bufOps decompress_pipe) filesInOneDataBlock processDir dir return dir ) blocks_info <- replicateM (length datablocks) (getP backdoor) arcpos <- archiveGetPos archive
writeControlBlock DIR_BLOCK dir_compressor $ do archiveWriteDir blocks_info arcpos receiveBuf sendBuf )
One transformation might be to get rid of the, if..then..else if.. like this: do dir <- case () of _ | copy_solid_block -> do sendP pipe (CopySolidBlock filesInOneDataBlock) return$ map fileWithCRC filesInOneDataBlock | (compressor==[aFAKE_COMPRESSION]) -> do sendP pipe (FakeFiles filesInOneDataBlock) return$ map (FileWithCRC 0 . cfFileInfo) filesInOneDataBlock | otherwise -> mapMaybeM (read_file command bufOps decompress_pipe) filesInOneDataBlock Not sure if that is actually better or not :) j.

Bulat Ziganshin wrote:
because REAL code is somewhat larger than examples. try to rewrite the following:
directory_blocks <- (`mapM` splitBy (opt_group_dir command) files_to_archive) ( \filesInOneDirectory -> do datablocks <- (`mapM` splitToSolidBlocks filesInOneDirectory) ( \filesInOneDataBlock -> do [...]
This particular snippet contains too many undefined identifiers to be rewritten effectively, but I'm very sure that the whole program can be restructured to great effect. Maybe by designing a "binary-block"-combinator language which calculates padding bytes and length headers automatically and fiddles out scheduling for fast writing to a pipe, something like that. Eventually, a binary parser combinator library which can read single bit flags and things is a must here. It may even be possible to combine the two providing a bijection between abstract file tree, "tar"-ed blocks and compressed binary file. Separate your concerns, ban IO as much as possible and any function that takes more than 15 lines is a wart. I admit that real world applications are not a good exercise to practice functional programming, but once acquired, advanced functional tactics prove very powerful. An example might be WASH/CGI which successfully abstracts session state over HTTP, a problem where Perl-Scripts are doomed and all kind of imperative buzz like JavaBeans and so on have been invented but somewhat fail to solve it for non-trivial cases. Regards, afpelmus

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? I'm pretty sure you need parser support to pull off something like this, if by "pull off" you mean providing this syntax with less lexical overhead than the pure Haskell code. You'll have $( ) from a macro invocation, and [| |] around the body, or putting the body in a string
Tim Newsham wrote: literal. TH is handy for metaprogramming, but not very good for syntax extension. As for syntax design, the original isn't so bad. The only thing truly useless are the parentheses or $. Some visual indication that args is being bound is nice, plus the \bindings notation scales nicely to constructs binding more names. "do" is arguable, at least it seems pretty popular to use something similar with loops in syntaxes heavier on keywords than symbols. Couldn't '\' delimit a subexpression, as parentheses do? Would there be any ambiguity in accepting code like State \s -> (s, s) instead of requiring State $ \s -> (s, s), or taking main = do args <- getArgs foreach args \arg -> do foreach [1..3] \n -> do putStrLn ((show n) ++ ") " ++ arg It would be a bit odd to have a kind of grouping the always starts explicitly and ends implicitly, but other than that it seems pretty handy, harmless, and natural (I know I've tried to write this sort of thing often enough) Brandon

Brandon Moore wrote:
Couldn't '\' delimit a subexpression, as parentheses do? Would there be any ambiguity in accepting code like State \s -> (s, s) instead of requiring State $ \s -> (s, s), or taking
main = do args <- getArgs foreach args \arg -> do foreach [1..3] \n -> do putStrLn ((show n) ++ ") " ++ arg
It would be a bit odd to have a kind of grouping the always starts explicitly and ends implicitly, but other than that it seems pretty handy, harmless, and natural (I know I've tried to write this sort of thing often enough)
Sounds like an extremely good idea to me. Ben

Couldn't '\' delimit a subexpression, as parentheses do? Would there be any ambiguity in accepting code like State \s -> (s, s) instead of requiring State $ \s -> (s, s), or taking
Looking at the Haskell 98 language definition it seems that a whole class of these expressions are disallowed inside function applications:
exp10 -> \ apat1 ... apatn -> exp | let decls in exp | if exp then exp else exp | case exp of { alts } | do { stmts } | fexp
This means that none of the following are legal Haskell declarations, even though they are unambiguous:
a = State \s -> (s, s) b = map let f x = x + 1 in f c = return if a then b else c d = catch do x <- getLine return x
It can be argued that this is mostly obfuscation, and that it can sometimes be confusing, especially with let and do, but it saves on the amount of parentheses or $s. What was the original reasoning for disallowing these more complex expressions as the rightmost argument in an fexp? Or was this simply not considered? Twan

foreach l f = mapM_ f l
... rename to forM_ as per previous emails ... I would like to add to this. The previous loop runs the code once independantly for each item in the list. Sometimes you want to carry state through the loop: v = init foreach x list do code v = update v (I know that this can be done with IORefs, but ignoring that for now) for looping with a carried variable: forXM_ init [] f = () forXM_ init (x:xs) f = do i' <- f init x forXM_ i' xs f or with a returned value (the carried variable at the end of the loop): forXM init [] f = init forXM init (x:xs) f = do i' <- f init x forXM i' xs f used as: forXM_ 0 [1,2,3,4] (\x n -> putStrLn $ unwords [show x, " -> ", show n] return $ x + n ) looping a fixed number of times when the loop index is not needed: loopM_ n f = forM_ [1..n] (\n -> f) used as: loopM_ 5 ( print "hello" ) with a carried variable (with and without a result): loopXM_ i n f = forXM_ i [1..n] (\x n -> f x) loopXM i n f = forXM i [1..n] (\x n -> f x) (is this related to foldM_?) used as: loopXM_ 1 5 (\x -> print x return (x * x + x) ) do..while loop with a carried variable: untilXM_ i p f = do i' <- f i when (p i') (untilXM_ f i') untilXM i p f = do i' <- f i if (p i') then (untilXM_ f i') else (return i') used as: untilXM_ 1 (< 100) (\x -> print x return (x * x + x) ) Some of these also make sense in pure-functional code (obviously not the ones with no return values). For example the following iteration with a loop-carried variable: s = 0 foreach n [1,2,3,4] s += n return s is "foldl (+) 0 [1,2,3,4]" and we can mimic the syntax by reordering the arguments: forX i l f = foldl f i l forX 0 [1,2,3,4] (\x n -> x + n ) Obviously many of these examples can be rewritten easily without using these constructs, but as was pointed out earlier in the thread, larger, more complicated programs are more difficult to juggle around. These constructs are fairly easy to understand, at least for people coming from an imperative background... I recently rewrote a small (a few hundred lines of code) imperative program in haskell using these constructs without changing the structure of the code very much. Maybe I'm missing the point somewhat (I'm still learning haskell) by trying to mimick imperative constructs in haskell, but the translation was much simpler (and mechanical) this way... Tim Newsham http://www.thenewsh.com/~newsham/

Hello Tim, Wednesday, September 13, 2006, 10:48:37 PM, you wrote:
I would like to add to this. The previous loop runs the code once independantly for each item in the list. Sometimes you want to carry state through the loop: ....
all this can be easily implemented by programmer himself. but we can't add our own syntax constructions. so it will be great to either add constructs that mimics existing imperative languages or a way to redefine syntax on-the-fly. second can be implemented by using Parsec-like parser in haskell compiler. i also seen a syntax macros for Haskell: http://www.cs.uu.nl/groups/ST/twiki/pub/Center/SyntaxMacros/sm_example.zip one project that adds syntax sugar for manipulating imperative arrays and hashes is http://www.isi.edu/~hdaume/STPP/stpp.tar.gz we can also develop some ideas that will allow user to extend language with imperative-friendly features. first, the problem is that Haskell requires to exactly specify order of evaluation. but in many cases it's not important - when we want to multiply values of two variables, it's no matter what variable will be read first. so, instead of a' <- val a b' <- val b c =: a' * b' we will prefer to write c =: a*b this involves a lot of problems with types and and need to redefine classes for every operation that can be used in such way second, we need to be able to define new keywords together with using layout statements in our constructs: for i in [1..n] while a[i]<0 do .... may be it should be just syntax-level macro which generates code like this: foreachCond [1..n] (a]i]<0) $ \i -> do and last problem is what code to generate for break/continue (goto? :) operations -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
we can also develop some ideas that will allow user to extend language with imperative-friendly features. first, the problem is that Haskell requires to exactly specify order of evaluation.
...
second, we need to be able to define new keywords together with using layout statements in our constructs:
and last problem is what code to generate for break/continue (goto? :) operation I realize Mr. Ziganshin has much more experience with Haskell than I (I only became aware of Haskell in the last year and I'm still struggling with the more advanced corners of the language.) But I have to respectfully disagree with these suggestions. At no point have I wished
... that Haskell adopt more from the imperative programming world! Others have already shown how "foreach" can be written in a functional manner. I think it's more important that we (the new members of the Haskell community) learn the language rather than make the language more familiar to imperative programmers. My exposure to Haskell (in its current form) motivated me to attend this year's ICFP conference. (I'm looking forward to attending the Haskell Workshop this Sunday.) -- Rich
participants (13)
-
apfelmus@quantentunnel.de
-
Benjamin Franksen
-
Brandon Moore
-
Bulat Ziganshin
-
dons@cse.unsw.edu.au
-
Henning Thielemann
-
Jeremy Shaw
-
Lemmih
-
Michael Shulman
-
Rich Neswold
-
Tim Newsham
-
Twan van Laarhoven
-
Udo Stenzel