[Haskell-cafe] Re: Time constrained computation

Roel van Dijk vandijk.roel at gmail.com
Fri Aug 28 12:58:36 EDT 2009


This is my go at the problem:


module Main where

import Control.Concurrent
import Data.IORef

-- From the Haskell wiki
primes :: [Integer]
primes = sieve [2..]
    where sieve (p:xs) = p : sieve [x | x <- xs, x `mod` p /= 0]

producePrimes :: IORef [Integer] -> IO ()
producePrimes ref = go primes
    where go (x:xs) = modifyIORef ref (\ys -> x:ys) >> go xs
          go []     = error "Euclid was wrong!"

-- Calculate as much primes as possible in 't' picoseconds
getPrimes :: Int -> IO [Integer]
getPrimes t = do ref <- newIORef []
                 producer <- forkIO (producePrimes ref)
                 threadDelay t
                 killThread producer
                 readIORef ref

main = do ps <- getPrimes 1000000
          print $ length ps


Or view my hpaste: http://hpaste.org/fastcgi/hpaste.fcgi/view?id=8782#a8782

If you run this a few times in GHCI you will find that it calculates
an increasingly large number of primes within the same time span. This
is because the previous results are retained. Compile and run or
restart GHCI for every run for accurate results.

On Fri, Aug 28, 2009 at 3:01 PM, Mitar<mmitar at gmail.com> wrote:
> Hi!
>
> Ups, missed save button and pressed send. ;-)
>
> So I am not really sure if this is correct term for it but I am open
> to better (search) terms.
>
> I am wondering if it is possible to make a time constrained
> computation. For example if I have a computation of an approximation
> of a value which can take more or less time (and you get more or less
> precise value) or if I have an algorithm which is searching some
> search-space it can find better or worse solution depending how much
> time you allow. So I would like to say to Haskell to (lazily, if it
> really needs it) get me some value but not to spend more than so much
> time calculating it.
>
> One abstraction of this would be to have an infinity list of values
> and I would like to get the last element I can get in t milliseconds
> of computational time.
>
> One step further would be to be able to stop computation not at
> predefined time but with some other part of the program deciding it is
> enough. So I would have a system which would monitor computation and a
> pure computation I would be able to stop. Is this possible? Is it
> possible to have a pure computation interrupted and get whatever it
> has computed until then?
>
> How could I make this? Is there anything already done for it? Some
> library I have not found?
>
> Of course all this should be as performance wise as it is possible.
>
> So the best interface for me would be to be able to start a pure
> computation and put an upper bound on computation time but also be
> able to stop it before that upper bound. And all this should be as
> abstracted as it is possible.
>
>
> Mitar
> _______________________________________________
> 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