wanted: Function to break circular data dependencies

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

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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
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
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@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

Doesn't ghc detect this with "black holes" or something? Maybe just catch http://hackage.haskell.org/package/base-4.7.0.0/docs/Control-Exception.html#... ? Cheers Ben Joey Adams wrote:
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
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
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
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@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
-- "Make it so they have to reboot after every typo." -- Scott Adams

Joey Adams
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
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
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@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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, May 4, 2014 at 3:39 PM, Mathijs Kwik
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]
To be more precise, I believe we're looking to catch an expression where evaluating it to head-normal form demands itself already evaluated in head-normal form. In your example, there is no loop because `length a` can be evaluated without evaluating any of the items in `a`. But you get an infinite loop if you make cons strict in the item: {-# LANGUAGE BangPatterns #-} import Prelude hiding (length) -- | List whose cons is strict in the value. data SList a = Nil | Cons !a (SList a) deriving Show infixr 5 `Cons` length :: SList a -> Int length xs0 = go 0 xs0 where go !n Nil = n go !n (Cons _ xs) = go (n+1) xs a :: SList Int a = (length a * 2) `Cons` (length a * 3) `Cons` (length a * 4) `Cons` Nil main :: IO () main = print a

Job Vranish
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?
This makes me think of the more widely-known 'parallel OR' operator, which evaluates its arguments in parallel and returns whichever finishes evaluating first. This operator cannot be implemented in Lambda Calculus, but it can in Haskell (via threads). Unfortunately Googling for 'haskell "parallel or"' brings up sentence fragments ('...parallel or concurrent...') rather than a parallel or implementation. You couldn't use parallel or as-is, since your "fallback" value will probably evaluate faster than your "real" value most of the time, but it may give you hints. Cheers, Chris

On Tue, May 6, 2014 at 11:38 AM, Chris Warburton
Job Vranish
writes: 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?
This makes me think of the more widely-known 'parallel OR' operator, which evaluates its arguments in parallel and returns whichever finishes evaluating first.
This operator cannot be implemented in Lambda Calculus, but it can in Haskell (via threads). Unfortunately Googling for 'haskell "parallel or"' brings up sentence fragments ('...parallel or concurrent...') rather than a parallel or implementation.
Perhaps you are looking for 'unamb' [0]? Erik [0] http://hackage.haskell.org/package/unamb

Great, I didn't know unamb! Specially the function "race" included:
race :: IOhttp://hackage.haskell.org/packages/archive/base/4.5.0.0/doc/html/System-IO....a
->
IOhttp://hackage.haskell.org/packages/archive/base/4.5.0.0/doc/html/System-IO....a
->
IOhttp://hackage.haskell.org/packages/archive/base/4.5.0.0/doc/html/System-IO....a
Race two actions against each other in separate threads, and pick whichever
finishes first. See also
ambhttp://hackage.haskell.org/package/unamb-0.2.5/docs/Data-Unamb.html#v:amb.
Could it be used to build a watchdog? Simply by providing one of the two
arguments as an action that waits and then gives a default value.
On Tue, May 6, 2014 at 12:24 PM, Erik Hesselink
On Tue, May 6, 2014 at 11:38 AM, Chris Warburton
wrote: Job Vranish
writes: 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?
This makes me think of the more widely-known 'parallel OR' operator, which evaluates its arguments in parallel and returns whichever finishes evaluating first.
This operator cannot be implemented in Lambda Calculus, but it can in Haskell (via threads). Unfortunately Googling for 'haskell "parallel or"' brings up sentence fragments ('...parallel or concurrent...') rather than a parallel or implementation.
Perhaps you are looking for 'unamb' [0]?
Erik
[0] http://hackage.haskell.org/package/unamb _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Just to say there is similar functionality in Marlow's async library:
http://hackage.haskell.org/package/async-2.0.1.5/docs/Control-Concurrent-Asy...
http://hackage.haskell.org/package/async-2.0.1.5/docs/Control-Concurrent-Asy...
Might overkill for your issue, but I thought it was worth mentioning it.
On 6 May 2014 12:48, Corentin Dupont
Great, I didn't know unamb! Specially the function "race" included:
race :: IOhttp://hackage.haskell.org/packages/archive/base/4.5.0.0/doc/html/System-IO....a -> IOhttp://hackage.haskell.org/packages/archive/base/4.5.0.0/doc/html/System-IO....a -> IOhttp://hackage.haskell.org/packages/archive/base/4.5.0.0/doc/html/System-IO....a Race two actions against each other in separate threads, and pick whichever finishes first. See also ambhttp://hackage.haskell.org/package/unamb-0.2.5/docs/Data-Unamb.html#v:amb.
Could it be used to build a watchdog? Simply by providing one of the two arguments as an action that waits and then gives a default value.
On Tue, May 6, 2014 at 12:24 PM, Erik Hesselink
wrote: On Tue, May 6, 2014 at 11:38 AM, Chris Warburton
wrote: Job Vranish
writes: 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?
This makes me think of the more widely-known 'parallel OR' operator, which evaluates its arguments in parallel and returns whichever finishes evaluating first.
This operator cannot be implemented in Lambda Calculus, but it can in Haskell (via threads). Unfortunately Googling for 'haskell "parallel or"' brings up sentence fragments ('...parallel or concurrent...') rather than a parallel or implementation.
Perhaps you are looking for 'unamb' [0]?
Erik
[0] http://hackage.haskell.org/package/unamb _______________________________________________ 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
-- *Alois Cochard* http://aloiscochard.blogspot.com http://twitter.com/aloiscochard http://github.com/aloiscochard

On Tue, May 6, 2014 at 11:48 PM, Corentin Dupont
Great, I didn't know unamb! Specially the function "race" included:
race :: IO a -> IO a -> IO a Race two actions against each other in separate threads, and pick whichever finishes first. See also amb.
Could it be used to build a watchdog? Simply by providing one of the two arguments as an action that waits and then gives a default value.
If you simply want a timeout, then I'd suggest System.Timeout instead[1] [1] http://hackage.haskell.org/package/base-4.7.0.0/docs/System-Timeout.html
On Tue, May 6, 2014 at 12:24 PM, Erik Hesselink
wrote: On Tue, May 6, 2014 at 11:38 AM, Chris Warburton
wrote: Job Vranish
writes: 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?
This makes me think of the more widely-known 'parallel OR' operator, which evaluates its arguments in parallel and returns whichever finishes evaluating first.
This operator cannot be implemented in Lambda Calculus, but it can in Haskell (via threads). Unfortunately Googling for 'haskell "parallel or"' brings up sentence fragments ('...parallel or concurrent...') rather than a parallel or implementation.
Perhaps you are looking for 'unamb' [0]?
Erik
[0] http://hackage.haskell.org/package/unamb _______________________________________________ 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

Job Vranish wrote:
Is a function like the following possible?:
avoidCircularDataDependency :: a -> a -> a avoidCircularDataDependency a b = ?
For one, it breaks purity. If we have let x = avoidCircularDataDependency y True y = avoidCircularDataDependency x False then whether x and y are True or False depends on which of them is evaluated first. Note that x and y might be evaluated in parallel by different threads. Secondly, an implementation of avoidCircularDataDependencies in a threaded runtime system requires cycle detection on the heap, because running into a black hole does not reliably indicate a data dependency cycle. GHC currently only does this when things have already gone wrong; cycles are detected during garbage collection and the threads involved receive NonTermination exceptions as a result. To make avoidCircularDataDependencies useful, you'd need a more efficient way of detecting cycles, which looks like a hard problem to me.
I've often found myself wanting a function like this. It would make certain kinds of knot-tying/cycle detection _much_ easier.
Actually I'd be interested in seeing an example for this. Cheers, Bertram
participants (10)
-
Alois Cochard
-
Ben Franksen
-
Bertram Felgenhauer
-
Chris Warburton
-
Chris Wong
-
Corentin Dupont
-
Erik Hesselink
-
Job Vranish
-
Joey Adams
-
Mathijs Kwik