Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread timothyhobbs
This seems like a bug in GHC. But it has nothing to do with MVars.  I've 
narrowed this down and filed a bug report here:

http://hackage.haskell.org/trac/ghc/ticket/7528

Timothy


-- Původní zpráva --
Od: Yuras Shumovich shumovi...@gmail.com
Datum: 24. 12. 2012
Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation

On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz wrote:
 The real question is, does this mean that GHC is stopping the world every 
 time it puts an MVar?

No, GHC rts only locks the MVar itself.
See here:
http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358
(http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358)

Yuras___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread Corentin Dupont
Hi Brandon,
indeed in my example if you add:
*b - evaluate a*
after the definition of a it works.
However, in my original program it doesn't work, I suppose because I
interpret the user submitted code (here *let (a::String) = a *
 for the example) via Hint and Hint-server, and the interpretation must be
done in another thread...

Best,
Corentin

On Mon, Dec 24, 2012 at 3:46 PM, Brandon Allbery allber...@gmail.comwrote:

 On Mon, Dec 24, 2012 at 8:45 AM, Corentin Dupont 
 corentin.dup...@gmail.com wrote:

 *execBlocking :: MVar (Maybe MyData) - IO ()
 execBlocking mv = do
let (a::String) = a
--If you uncomment the next line, it will work
--putStrLn $ show a
putMVar mv (Just $ MyData a toto)*


 It's laziness, yes; you need to do something along the lines of

  let a = length a `seq` a

 or possibly Control.Exception.evaluate needs to be involved somewhere.

 --
 brandon s allbery kf8nh   sine nomine
 associates
 allber...@gmail.com
 ballb...@sinenomine.net
 unix, openafs, kerberos, infrastructure, xmonad
 http://sinenomine.net

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread Corentin Dupont
Great, with me compiled with ghc -threaded the bug shows up.
However, runnning main in ghci doesn't show the bug (it finishes
correctly).
I have GHC 7.4.1.

Corentin

On Tue, Dec 25, 2012 at 3:34 PM, timothyho...@seznam.cz wrote:

 This seems like a bug in GHC. But it has nothing to do with MVars.  I've
 narrowed this down and filed a bug report here:

 http://hackage.haskell.org/trac/ghc/ticket/7528

 Timothy

 -- Původní zpráva --
 Od: Yuras Shumovich shumovi...@gmail.com

 Datum: 24. 12. 2012
 Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation


 On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz wrote:
  The real question is, does this mean that GHC is stopping the world
 every
  time it puts an MVar?

 No, GHC rts only locks the MVar itself.
 See here:
 http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358

 Yuras


 ___
 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


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread timothyhobbs
I'm not sure that there is anything great about this bug.  It seems to me 
to be a rather severe demonstration of a somewhat already known design flaw 
in the runtime :(

Could you please comment on the actual bug rather than replying here so that
the devs see that this behaviour has been confirmed?

Tim


-- Původní zpráva --
Od: Corentin Dupont corentin.dup...@gmail.com
Datum: 25. 12. 2012
Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation



Great, with me compiled with ghc -threaded the bug shows up.

However, runnning main in ghci doesn't show the bug (it finishes 
correctly).

I have GHC 7.4.1.

 

Corentin
 


On Tue, Dec 25, 2012 at 3:34 PM, timothyho...@seznam.cz
(mailto:timothyho...@seznam.cz) wrote:
 
This seems like a bug in GHC. But it has nothing to do with MVars.  I've 
narrowed this down and filed a bug report here:

http://hackage.haskell.org/trac/ghc/ticket/7528
(http://hackage.haskell.org/trac/ghc/ticket/7528)

Timothy


-- Původní zpráva --
Od: Yuras Shumovich shumovi...@gmail.com(mailto:shumovi...@gmail.com)


Datum: 24. 12. 2012
Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation




On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz
(mailto:timothyho...@seznam.cz) wrote:
 The real question is, does this mean that GHC is stopping the world every 
 time it puts an MVar?

No, GHC rts only locks the MVar itself.
See here:
http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358
(http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358)

Yuras




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org(mailto:Haskell-Cafe@haskell.org)
http://www.haskell.org/mailman/listinfo/haskell-cafe
(http://www.haskell.org/mailman/listinfo/haskell-cafe)




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-25 Thread Yuras Shumovich
Hi,

AFAIK it is (partially?) fixed in HEAD, see
http://hackage.haskell.org/trac/ghc/ticket/367

It works for me with -fno-omit-yields

Thanks,
Yuras

On Tue, 2012-12-25 at 19:35 +0100, timothyho...@seznam.cz wrote:
 I'm not sure that there is anything great about this bug.  It seems to me 
 to be a rather severe demonstration of a somewhat already known design flaw 
 in the runtime :(
 
 Could you please comment on the actual bug rather than replying here so that
 the devs see that this behaviour has been confirmed?
 
 Tim
 
 
 -- Původní zpráva --
 Od: Corentin Dupont corentin.dup...@gmail.com
 Datum: 25. 12. 2012
 Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation
 
 
 
 Great, with me compiled with ghc -threaded the bug shows up.
 
 However, runnning main in ghci doesn't show the bug (it finishes 
 correctly).
 
 I have GHC 7.4.1.
 
  
 
 Corentin
  
 
 
 On Tue, Dec 25, 2012 at 3:34 PM, timothyho...@seznam.cz
 (mailto:timothyho...@seznam.cz) wrote:
  
 This seems like a bug in GHC. But it has nothing to do with MVars.  I've 
 narrowed this down and filed a bug report here:
 
 http://hackage.haskell.org/trac/ghc/ticket/7528
 (http://hackage.haskell.org/trac/ghc/ticket/7528)
 
 Timothy
 
 
 -- Původní zpráva --
 Od: Yuras Shumovich shumovi...@gmail.com(mailto:shumovi...@gmail.com)
 
 
 Datum: 24. 12. 2012
 Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation
 
 
 
 
 On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz
 (mailto:timothyho...@seznam.cz) wrote:
  The real question is, does this mean that GHC is stopping the world every 
  time it puts an MVar?
 
 No, GHC rts only locks the MVar itself.
 See here:
 http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358
 (http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358)
 
 Yuras
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org(mailto:Haskell-Cafe@haskell.org)
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 (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] multi-thread and lazy evaluation

2012-12-24 Thread Corentin Dupont
Hi all,
I have a program where the user can submit his own little programs, which
are interpreted using Hint. The user-submitted programs are used to modify
a state held in a TVar.
As of course those user-submitted programs can't be trusted, I'm trying to
protect them, like in Mueval.
I installed a watchdog to monitor and kill the user's thread if it doesn't
finish. However it doesn't work properly, due to lazy evaluation I believe.
I made a little exemple to illustrate the problem.

- The following program doesn't terminate, but if you uncomment the
putStrLn at the end, it will.
Could someone explain me this and how to do it properly??

Merry Christmas to all
Corentin
*
{-# LANGUAGE ScopedTypeVariables #-}

import Control.Concurrent.STM.TVar
import Control.Concurrent.MVar
import Control.Concurrent
import Control.Monad.STM

data MyData = MyData { a :: String, b :: String } deriving (Show)

main = do
   tv - atomically $ newTVar $ MyData a b
   protectedExecCommand tv
   myNewData - atomically $ readTVar tv
   putStrLn $ show myNewData


protectedExecCommand :: (TVar MyData) - IO ()
protectedExecCommand tv = do
mv - newEmptyMVar
before - atomically $ readTVar tv
id - forkIO $ execBlocking mv
forkIO $ watchDog' 5 id mv
res - takeMVar mv
case res of
   Nothing - (atomically $ writeTVar tv before)
   Just after - (atomically $ writeTVar tv after)

watchDog' :: Int - ThreadId - MVar (Maybe x) - IO ()
watchDog' t tid mv = do
   threadDelay $ t * 100
   killThread tid
   putStrLn $ process timeout 
   tryPutMVar mv Nothing
   return ()

execBlocking :: MVar (Maybe MyData) - IO ()
execBlocking mv = do
   let (a::String) = a
   --If you uncomment the next line, it will work
   --putStrLn $ show a
   putMVar mv (Just $ MyData a toto)*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-24 Thread Corentin Dupont
Sorry, I'm thinking my example program wasn't maybe too explicit.
In it, the line *let (a::String) = a* represents the program submitted by
the user, that is faulty.
The objective is to stop it after some time, and set the (TVar MyData) to
its previous value.
As you can see, it works only if I put a putStrLn in the same thread to
force the evaluation

*{-# LANGUAGE ScopedTypeVariables #-}

import Control.Concurrent.STM.TVar
import Control.Concurrent.MVar
import Control.Concurrent
import Control.Monad.STM

data MyData = MyData { a :: String, b :: String } deriving (Show)

main = do
   tv - atomically $ newTVar $ MyData a b
   protectedExecCommand tv
   myNewData - atomically $ readTVar tv
   putStrLn $ show myNewData


protectedExecCommand :: (TVar MyData) - IO ()
protectedExecCommand tv = do
mv - newEmptyMVar
before - atomically $ readTVar tv
id - forkIO $ execBlocking mv
forkIO $ watchDog' 5 id mv
res - takeMVar mv
case res of
   Nothing - (atomically $ writeTVar tv before)
   Just after - (atomically $ writeTVar tv after)

watchDog' :: Int - ThreadId - MVar (Maybe x) - IO ()
watchDog' t tid mv = do
   threadDelay $ t * 100
   killThread tid
   putStrLn $ process timeout 
   tryPutMVar mv Nothing
   return ()

execBlocking :: MVar (Maybe MyData) - IO ()
execBlocking mv = do
   let (a::String) = a
   --If you uncomment the next line, it will work
   --putStrLn $ show a
   putMVar mv (Just $ MyData a toto)*

On Mon, Dec 24, 2012 at 1:17 PM, Corentin Dupont
corentin.dup...@gmail.comwrote:

 Hi all,
 I have a program where the user can submit his own little programs, which
 are interpreted using Hint. The user-submitted programs are used to modify
 a state held in a TVar.
 As of course those user-submitted programs can't be trusted, I'm trying to
 protect them, like in Mueval.
 I installed a watchdog to monitor and kill the user's thread if it doesn't
 finish. However it doesn't work properly, due to lazy evaluation I believe.
 I made a little exemple to illustrate the problem.

 - The following program doesn't terminate, but if you uncomment the
 putStrLn at the end, it will.
 Could someone explain me this and how to do it properly??

 Merry Christmas to all
 Corentin
 *
 {-# LANGUAGE ScopedTypeVariables #-}

 import Control.Concurrent.STM.TVar
 import Control.Concurrent.MVar
 import Control.Concurrent
 import Control.Monad.STM

 data MyData = MyData { a :: String, b :: String } deriving (Show)

 main = do
tv - atomically $ newTVar $ MyData a b
protectedExecCommand tv
myNewData - atomically $ readTVar tv
putStrLn $ show myNewData


 protectedExecCommand :: (TVar MyData) - IO ()
 protectedExecCommand tv = do
 mv - newEmptyMVar
 before - atomically $ readTVar tv
 id - forkIO $ execBlocking mv
 forkIO $ watchDog' 5 id mv
 res - takeMVar mv
 case res of
Nothing - (atomically $ writeTVar tv before)
Just after - (atomically $ writeTVar tv after)

 watchDog' :: Int - ThreadId - MVar (Maybe x) - IO ()
 watchDog' t tid mv = do
threadDelay $ t * 100
killThread tid
putStrLn $ process timeout 
tryPutMVar mv Nothing
return ()

 execBlocking :: MVar (Maybe MyData) - IO ()
 execBlocking mv = do
let (a::String) = a
--If you uncomment the next line, it will work
--putStrLn $ show a
putMVar mv (Just $ MyData a toto)*

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-24 Thread Brandon Allbery
On Mon, Dec 24, 2012 at 8:45 AM, Corentin Dupont
corentin.dup...@gmail.comwrote:

 *execBlocking :: MVar (Maybe MyData) - IO ()
 execBlocking mv = do
let (a::String) = a
--If you uncomment the next line, it will work
--putStrLn $ show a
putMVar mv (Just $ MyData a toto)*


It's laziness, yes; you need to do something along the lines of

 let a = length a `seq` a

or possibly Control.Exception.evaluate needs to be involved somewhere.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-24 Thread timothyhobbs
The real question is, does this mean that GHC is stopping the world every 
time it puts an MVar?

Tim

-- Původní zpráva --
Od: Brandon Allbery allber...@gmail.com
Datum: 24. 12. 2012
Předmět: Re: [Haskell-cafe] multi-thread and lazy evaluation



On Mon, Dec 24, 2012 at 8:45 AM, Corentin Dupont corentin.dup...@gmail.com
(mailto:corentin.dup...@gmail.com) wrote:

 

execBlocking :: MVar (Maybe MyData) - IO ()
execBlocking mv = do
   let (a::String) = a 
   --If you uncomment the next line, it will work
   --putStrLn $ show a
   putMVar mv (Just $ MyData a toto)





It's laziness, yes; you need to do something along the lines of




 let a = length a `seq` a




or possibly Control.Exception.evaluate(http://Control.Exception.evaluate) 
needs to be involved somewhere.

 

-- 


brandon s allbery kf8nh                               sine nomine associates

allber...@gmail.com(mailto:allber...@gmail.com)                             
     ballb...@sinenomine.net(mailto:ballb...@sinenomine.net)

unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
(http://sinenomine.net)
 


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] multi-thread and lazy evaluation

2012-12-24 Thread Yuras Shumovich
On Mon, 2012-12-24 at 16:16 +0100, timothyho...@seznam.cz wrote:
 The real question is, does this mean that GHC is stopping the world every 
 time it puts an MVar?

No, GHC rts only locks the MVar itself.
See here:
http://hackage.haskell.org/trac/ghc/browser/rts/PrimOps.cmm#L1358

Yuras


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe