Re: Re[4]: [Haskell-cafe] REALLY simple STRef examples

The IO monad hasn't given me too much trouble, but I want to be sure
to structure things the way "they should be". If I get everything
running using IO first and then have type-checking problems with ST,
it will be tempting to just slap on an unsafePerformIO and call it
good. Sure, it's really doing the same thing anyway, but it just comes
out looking like a hack.
On 7/20/06, Bulat Ziganshin
Hello Chad,
Friday, July 21, 2006, 12:26:58 AM, you wrote:
Ok, I see now why the return is necessary.
btw, it may be helpful to read "IO inside" material. ST monad is not very different from IO monad - it only limited to operations on STRef and STArray, so that it can't have side-effects visible outside of runST statement used to run ST computation

Not totally relevant to what the discussion has evolved to, but I wrote a factorial function using STRefs (in the spirit of the Evolution of a Haskell programmer) and I think it qualifies as a really simple example. Code follows: import Data.STRef import Control.Monad.ST foreach :: (Monad m) => [a] -> (a -> m b) -> m () foreach = flip mapM_ -- Bryn Keller's foreach, but with type restrictions fac :: (Num a, Enum a) => a -> a fac n = runST (fac' n) fac' :: (Num a, Enum a) => a -> ST s a fac' n = do r <- newSTRef 1 foreach [1..n] (\x -> modifySTRef r (*x)) x <- readSTRef r return x Chad Scherrer wrote:
The IO monad hasn't given me too much trouble, but I want to be sure to structure things the way "they should be". If I get everything running using IO first and then have type-checking problems with ST, it will be tempting to just slap on an unsafePerformIO and call it good. Sure, it's really doing the same thing anyway, but it just comes out looking like a hack.
On 7/20/06, Bulat Ziganshin
wrote: Hello Chad,
Friday, July 21, 2006, 12:26:58 AM, you wrote:
Ok, I see now why the return is necessary.
btw, it may be helpful to read "IO inside" material. ST monad is not very different from IO monad - it only limited to operations on STRef and STArray, so that it can't have side-effects visible outside of runST statement used to run ST computation
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 7/21/06, S C Kuo
Not totally relevant to what the discussion has evolved to, but I wrote a factorial function using STRefs (in the spirit of the Evolution of a Haskell programmer) and I think it qualifies as a really simple example. Code follows:
import Data.STRef import Control.Monad.ST
foreach :: (Monad m) => [a] -> (a -> m b) -> m () foreach = flip mapM_ -- Bryn Keller's foreach, but with type restrictions
fac :: (Num a, Enum a) => a -> a fac n = runST (fac' n)
fac' :: (Num a, Enum a) => a -> ST s a fac' n = do r <- newSTRef 1 foreach [1..n] (\x -> modifySTRef r (*x)) x <- readSTRef r return x
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]
? I tried it out in GHCi, and it worked fine, and I have seen code that has been defined as a flip to take advantage of partial application. But your code doesn't seem to take advantage of partial application, so why did you define 'foreach' and then use it instead of using 'mapM_'? I am just curious, and have always been interested in reasons behind coding style. Bryan Burgers

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 -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

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
participants (5)
-
Bryan Burgers
-
Bulat Ziganshin
-
Chad Scherrer
-
S C Kuo
-
Shao Chih Kuo