[Haskell-cafe] "automonadization" of code?

Cale Gibbard cgibbard at gmail.com
Tue Dec 12 10:21:00 EST 2006


Well, there's the Haskell Array Preprocessor
(http://www.cs.utah.edu/~hal/APP/index.html), but I've never really
used it. I think the first thing to notice is that Control.Monad
really does contain a lot of functions which are useful control
structures. The way that you wrote that loop seems extremely awkward
to me. How I'd write it would be something like:

import Control.Monad
import Data.Array.IO

main = do
    a <- (newArray (1,100) 1) :: IO (IOArray Int Int)
    forM [2..99] $ \i -> do
       v <- liftM2 (+) (readArray a (i-1)) (readArray a (i+1))
       writeArray a i v
    print =<< getAssocs a

(Note that forM = flip mapM is a recent addition to Control.Monad)

It's possible to go quite a way to cleaning things up just using
appropriate functions.

On 12/12/06, Adam Megacz <megacz at cs.berkeley.edu> wrote:
>
> Is there any work on automatic translation of code in some tiny
> imperative language into Haskell code that uses the ST and/or IO
> monads (or perhaps even pure functional code)?
>
> For example, the user writes something vaguely like
>
>    array = newArray (1,100) 1
>    for x=2 to 99
>      array[x] := array[x-1]+array[x+1]
>
> And it is transformed into something like
>
>    foldl
>      (>>=)
>      (newArray (1,100) 1)
>      $ map (\n arr -> do a <- readArray arr (n-1)
>                          b <- readArray arr (n+1)
>                          writeArray     arr n     (a+b)
>                          return arr)
>            [2..99]
>
> Obviously the "small imperative language" would have to be highly
> restricted and carefully chosen in order for the translation to always
> work and be predictable.  I'm interested in any existing work on
> choosing such a sublanguage.
>
> Thanks!
>
>   - a
>
> --
> PGP/GPG: 5C9F F366 C9CF 2145 E770  B1B8 EFB1 462D A146 C380
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list