I tried this using timeout, but was never able to get it to work. The timeout doesn't behave like I expect. I can take several seconds for it to timeout, even with very low timeouts.
Any ideas?
- Job
module Main where
import Data.IORef
import System.Timeout
import System.IO.Unsafe
tailScan f (x:xs) = resultList
where
resultList = x : zipWith f resultList xs
facts = 1 : tailScan (*) [1..]
fac n = facts !! n
eterm x n = x^n / (fac n)
eseries x = fmap (eterm x) [0..]
ePrecisionList x = tailScan (+) $ eseries x
computeUntil t xs = do
a <- newIORef undefined
timeout t $ sequence $ fmap (writeIORef a) xs
readIORef a
-- compute e for only 10 microseconds
e x = computeUntil 10 (ePrecisionList x)
main = do
-- compute e
print =<< e 1
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe