Yes, largely the choice to define foreach was made to try and make it
look more imperative, I showed it to an imperative programmer to try and
convince him that you could program in an imperative way in Haskell if
you really wanted to, that and I thought it'd an imperative style would
make an interesting addition to the evolution of a Haskell programmer.
Bulat Ziganshin wrote:
Hello Bryan,
Saturday, July 22, 2006, 4:40:58 AM, you wrote:
Forgive me for not understanding, but I was hoping you would explain a
choice you made in your code. Why did you define foreach and then use
foreach [1..n] (\x -> modifySTRef r (*x))
Instead of simply using
mapM_ (\x -> modifySTRef r (*x)) [1..n]
because it looks just like for/foreach loops in imperative languages.
look at this:
import Control.Monad
import Data.IORef
infixl 0 =:, +=, -=, .=, <<=
ref = newIORef
val = readIORef
a=:b = writeIORef a b
a+=b = modifyIORef a (\a-> a+b)
a-=b = modifyIORef a (\a-> a-b)
a.=b = ((a=:).b) =<< val a
for :: [a] -> (a -> IO b) -> IO ()
for = flip mapM_
newList = ref []
list <<= x = list =:: (++[x])
push list x = list =:: (x:)
pop list = do x:xs<-val list; list=:xs; return x
main = do
sum <- ref 0
lasti <- ref undefined
for [1..5] $ \i -> do
sum += i
lasti =: i
sum .= (\sum-> 2*sum+1)
print =<< val sum
print =<< val lasti
xs <- newList
for [1..3] (push xs)
xs <<= 10
xs <<= 20
print =<< val xs
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe