[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


[Haskell-cafe] Foreign.Erlang help

2012-12-24 Thread Junior White
Hi all,
  I have a game server programming in erlang, but now i want to write some
game logic in haskell, how to write a haskell node for erlang?

  ps:I have read the introduce of Foreign.Erlang,I use haskell send a
message to a erlang echo server, but the server not receive anything.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Virthualenv/HsEnv in Windows

2012-12-24 Thread Kyle Hanson
Has anyone gotten this to work on Windows either native or on cygwin? Is
there an alternative?

Happy Holidays,
Kyle Hanson
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Substituting values

2012-12-24 Thread Radical
On Sat, Dec 22, 2012 at 12:35 AM, Kim-Ee Yeoh k...@atamo.com wrote:

 This is reminiscent of the Either (exception) monad where Left values, the
 exceptions, pass through unaltered, and Right values are transformable,
 i.e. acted on by functions.


Interesting. I hadn't thought of that parallel. But yes, I think it's a
similar notion of: transform the value only in one (or more) cases. It's
also similar to the Maybe monad in that I'm looking for something akin to
fromMaybe, but without having to place the value in a Maybe.


 But I have no idea what you're trying to achieve in the bigger picture.
 Help us help you by fleshing out your use case.


I'm not sure the bigger picture is helpful, but, for example, the last case
was something like:

  if ch == '\n' then ' ' else ch

I think I ended up rewriting it as something like:

  replace '\n' = ' '
  replace ch = ch

Which is straightforward enough, though it feels to me like there's too
much syntax involved.

Thanks,

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


Re: [Haskell-cafe] Substituting values

2012-12-24 Thread Radical
Yeah, I guess I was wondering whether something like it already existed.
Thinking about it some more, perhaps what I want is `tr` [1]. E.g.

  tr [Foo] [Bar]

Incorporating your suggestion would then yield a more general version like:

  trBy (== Foo) Bar



[1] http://en.wikipedia.org/wiki/Tr_(Unix)


On Sat, Dec 22, 2012 at 6:46 AM, David Thomas davidleotho...@gmail.comwrote:

 Seems like the function is easy to define:

 replaceIfEq a b c = if c == a then b else c

 Then the above can be written

replaceIfEq Foo Bar value

 Or the slightly more general (in exchange for slightly more verbosity at
 the call site)

 replaceIf p r a = if p a then r else a

replaceIf (== Foo) Bar value




 On Fri, Dec 21, 2012 at 6:46 PM, Radical radi...@google.com wrote:

 Sometimes I'll need something like:

   if value == Foo then Bar else value

 Or some syntactic variation thereof:

   case value of { Foo - Bar; _ - value }

 Is there a better/shorter way to do it? I'm surprised that it's more
 complicated to substitute a value on its own than e.g. in a list, using
 filter. Or perhaps I'm missing the right abstraction?

 Thanks,

 Alvaro




 ___
 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] Is OpenAL unqueueBuffers implemented correctly?

2012-12-24 Thread alex
Hi, there's no maintainer listed for the OpenAL package, so I'm posting 
here in hopes of finding the right person.

The unqueueBuffers function in Sound.OpenAL.AL.Source has the type

Source - [Buffer] - IO ()

but I think the type should be

Source - Int - IO [Buffer]

This wraps the function alSourceUnqueueBuffers which uses the array of 
buffers as an output argument. With the current implementation, it's 
impossible to get the list of buffers that were unqueued. This 
implementation works the way I expect:

unqueueBuffers :: AL.Source - Int - IO [AL.Buffer]
unqueueBuffers source nbuffers =
allocaArray nbuffers $ \ptr - do 
  alSourceUnqueueBuffers source (fromIntegral nbuffers) ptr
  peekArray nbuffers ptr

I just started using OpenAL, so I might be misunderstanding how this is 
supposed to work.

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