Not all recursive functions are infinite loops... In general it's impossible to detect an infinite loop: it's the "Halting Problem".But maybe it's also possible to forbid any recursive program by analysing the AST?
IMO, the only way to do that is with a watchdog. You launch the evaluation in a separate thread, watch it, and if it doesn't finish you kill it and return a default value.
I've used a watchdog in Nomyx (inspired from Mueval):
--Sets a watchdog to kill the evaluation thread if it doesn't finishes.
-- The function starts both the evaluation thread and the watchdog thread, and blocks awaiting the result.
-- Option 1: the evaluation thread finishes before the watchdog. The MVar is filled with the result,
-- which unblocks the main thread. The watchdog then finishes latter, and fills the MVar with Nothing.
-- Option 2: the watchdog finishes before the evaluation thread. The eval thread is killed, and the
-- MVar is filled with Nothing, which unblocks the main thread. The watchdog finishes.
evalWithWatchdog' :: NFData a => IO a -> IO (Maybe a)
evalWithWatchdog' s = do
mvar <- newEmptyMVar
hSetBuffering stdout NoBuffering
--start evaluation thread
id <- forkOS $ do
s' <- s
let s'' = force s'
putMVar mvar (Just s'')
--start watchdog thread
forkIO $ watchDog 3 id mvar
takeMVar mvar
-- | Fork off a thread which will sleep and then kill off the specified thread.
watchDog :: Int -> ThreadId -> MVar (Maybe a) -> IO ()
watchDog tout tid mvar = do
threadDelay (tout * 1000000)
killThread tid
putMVar mvar NothingOn Sun, May 4, 2014 at 6:00 PM, Job Vranish <job.vranish@gmail.com> wrote:
_______________________________________________Is a function like the following possible?:
avoidCircularDataDependency :: a -> a -> aavoidCircularDataDependency a b = ?I want avoidCircularDataDependency to evaluate 'a', but if in the process of evaluating 'a' its own result is demanded (which normally would result in an infinite loop) it returns 'b' otherwise it returns 'a' .I've often found myself wanting a function like this. It would make certain kinds of knot-tying/cycle detection _much_ easier.Is there any reason why this function can't/shouldn't exist?- Job
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe