[Haskell-cafe] different behaviours with or without putStrLn

James ‘Twey’ Kay twey at twey.co.uk
Sun Jan 12 22:49:04 UTC 2014


You can (probably) automatically derive it via Template Haskell using 
the deepseq-th package:

     {-# LANGUAGE TemplateHaskell #-}
     import Control.DeepSeq.TH

     data MyState = ...

     $(deriveNFData ''MyState)


On 2014-01-12 22:26, Corentin Dupont wrote:
> deepseq seems interresting (didn't know it).
> Do I have to create instances of NFData [2] for all my types? Too bad
> it's not derivable.
> 
> On Sun, Jan 12, 2014 at 11:10 PM, Ben Foppa <benjamin.foppa at gmail.com>
> wrote:
> 
>> Depending on the kind of state, WHNF may not be enough - have you
>> tried with deepseq?
>> 
>> On Sun, Jan 12, 2014 at 5:07 PM, Corentin Dupont
>> <corentin.dupont at gmail.com> wrote:
>> 
>>> Hi guys,
>>> I'm experimenting different behaviours with or without a
>>> "putStrLn"! :(
>>> 
>>> Basically, with the following code, I want the evaluation to
>>> really happen on the "evaluate".
>>> 
>>> I found out that it doesn't: it is evaluated elsewhere (I don't
>>> know where).
>>> 
>>> If I put a putStrLn (commented below), the evaluation really
>>> happens there.
>>> 
>>> execCommand :: (TVar MyState) -> StateT MyState IO () -> IO ()
>>> execCommand ts sm = do
>>>    s <- atomically $ readTVar ts
>>>    s' <- execStateT sm s
>>>    s'' <- evaluate s'          --evaluation should
>>> happen here, but it doesn't
>>>    --putStrLn $ displayMulti $ _multi s''
>>>    atomically $ writeTVar ts s''
>>> 
>>> To give you more context, I have a state that, when evaluated,
>>> might not terminate.
>>> So I added a watchdog (like in mueval), that will kill the thread
>>> in case the evaluation doesn't terminate.
>>> 
>>> That's why I need to be sure of where the evaluation takes place.
>>> 
>>> Thanks!
>>> 
>>> Corentin
>>> 
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe [1]
> 
> 
> 
> Links:
> ------
> [1] http://www.haskell.org/mailman/listinfo/haskell-cafe
> [2]
> http://hackage.haskell.org/package/deepseq-1.3.0.2/docs/Control-DeepSeq.html#t:NFData
> 
> _______________________________________________
> 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