[Haskell-cafe] wanted: Function to break circular data dependencies

Mathijs Kwik mathijs at bluescreen303.nl
Sun May 4 19:39:52 UTC 2014


Joey Adams <joeyadams3.14159 at gmail.com> writes:

> Job isn't trying to solve the halting problem, but to catch a specific type
> of infinite loop--an expression that demands itself in its own evaluation.
> Example:
>
>     fix (\n -> n+1) :: Int

An expression that demands itself isn't necessarily an infinite loop
either. So this still boils down to the halting problem.

a :: [Int]
a = [length a * 2, length a * 3, length a * 4]


>
> This produces an infinite loop (or throws NonTermination) because to
> evaluate n, you have to evaluate n and then do something to the result.
>
> On Sun, May 4, 2014 at 12:36 PM, Corentin Dupont
> <corentin.dupont at gmail.com>wrote:
>
>> Not all recursive functions are infinite loops... In general it's
>> impossible to detect an infinite loop: it's the "Halting Problem".
>> 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.
>> But maybe it's also possible to forbid any recursive program by analysing
>> the AST?
>>
>> 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 Nothing
>>
>>
>> On Sun, May 4, 2014 at 6:00 PM, Job Vranish <job.vranish at gmail.com> wrote:
>>
>>> Is a function like the following possible?:
>>>
>>> avoidCircularDataDependency :: a -> a -> a
>>> avoidCircularDataDependency 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 at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
> _______________________________________________
> 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