[Haskell-cafe] Proposal: Non-recursive let

Andreas Abel andreas.abel at ifi.lmu.de
Mon Jul 22 10:14:10 CEST 2013


Just today, my student asked me why the following program does nothing:

{-# LANGUAGE CPP, GeneralizedNewtypeDeriving, BangPatterns #-}

import Control.Monad
import System.IO.Unsafe
import Data.Array.IO
import Data.IORef
import Debug.Trace


type LinearArray a = (Int, IORef Int, IOArray Int a)

initLinearArray :: Int -> a -> LinearArray a
initLinearArray l a =
   trace "init" (
    unsafePerformIO (do version <- newIORef 0
                        array <- newArray (0, l - 1) a
                        return (0, version, array)))

readLinearArray :: Int -> (LinearArray a) -> a
readLinearArray l !(ver, realver, arr) =
   trace "read" (
    unsafePerformIO (do version <- readIORef realver
                        element <- readArray arr l
                        if (version == ver) then
                          return element
                          else error "Non-Linear read of linear Array"))

writeLinearArray :: Int -> a -> LinearArray a -> LinearArray a
writeLinearArray l e !(ver, realver, arr) =
   trace "write" (
    unsafePerformIO (do version <- readIORef realver
                        if (version == ver)
                          then
                          do writeIORef realver $ ver + 1
                             writeArray arr l e
                             return (ver + 1, realver, arr)
                          else error "Non-Linear write of linear Array"))

linearArrayToList :: Int -> Int -> (LinearArray a) -> [a]
linearArrayToList c m !a =
   trace "toList" (
     if (c >= m) then []
     else (readLinearArray c a) : (linearArrayToList (c + 1) m a))

eratostenesTest :: Int -> [Bool]
eratostenesTest length =
   let
     strikeMult :: Int -> Int -> Int -> (LinearArray Bool) -> 
(LinearArray Bool)
     strikeMult div cur len arr = trace "smStart" (
       if (cur >= len)
       then trace "arr" arr
       else let arr = trace "write" $ writeLinearArray cur False arr
            in trace "strikeMult2" $ strikeMult div (cur + div) len arr)
     nextPrime :: Int -> Int -> (LinearArray Bool) -> (LinearArray Bool)
     nextPrime cur len !arr =
       if (cur >= len)
       then
         arr
       else if (readLinearArray cur arr)
            then
              let arr = trace "strikeMult" $ strikeMult cur (cur + cur) 
len arr
              in trace "nextPrime" $ nextPrime (cur + 1) len arr
            else
              nextPrime (cur + 1) len arr
     ini = trace "ini" (initLinearArray length True)
     theArray = trace "nextPrimeCall" $ nextPrime 2 length ini
   in
    linearArrayToList 0 length theArray

On 22.07.13 9:01 AM, Richard A. O'Keefe wrote:
>
> On 21/07/2013, at 7:36 AM, Evan Laforge wrote:
>> Just by coincidence, I recently wrote this:
>
> This is a BEAUTIFUL example.
> I think we may disagree about what it's an example OF,
> however.  I found the code a little difficult to
> follow, but when that's fixed up, there's no longer
> any reason to want non-recursive let, OR a monad.
>
> I've run out of time tonight, but hope to say more tomorrow.
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

-- 
Andreas Abel  <><      Du bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.abel at ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/




More information about the Haskell-Cafe mailing list