
Hello, laziness just gave me some headache now. Because some of my code was evaluated much later, well first the memory use exploded but also I got an error which was really difficult to understand because it manifested much later than I would intuitively expect (when I read the record field, not when I wrote it...). Now, if nothing else for space usage needs, I need to make this strict. At first I tried bang patterns on my record: {-# LANGUAGE BangPatterns #-} data TvShow = TvShow { channel :: Channel, title :: !T.Text, startTime :: !T.Text, summary :: !T.Text } deriving (Eq, Show) That did not help. Then I tried deepseq: instance NFData TvShow return $!! result That did not help. And here's the catch: doing BOTH helps... I mean I think I'll check it again because I find it hard to believe but right now it really seems it behaves like that... Is that possible? That I need to combine BOTH deepseq and bang patterns to actually get my code to evaluate when filling in the data? Or am I going crazy? Thank you! Emmanuel

to be clear: I definitely have strict evaluation now. It works. And it
helped me to fix my bug (it's fixed now).
But I think that to actually get strict evaluation I needed BOTH bang
patterns AND deep seq, at that same time... Which seems strange to me, I
would think that either would suffice.
emmanuel
On Tue, Dec 25, 2012 at 1:17 PM, Emmanuel Touzery
Hello,
laziness just gave me some headache now. Because some of my code was evaluated much later, well first the memory use exploded but also I got an error which was really difficult to understand because it manifested much later than I would intuitively expect (when I read the record field, not when I wrote it...).
Now, if nothing else for space usage needs, I need to make this strict.
At first I tried bang patterns on my record:
{-# LANGUAGE BangPatterns #-}
data TvShow = TvShow { channel :: Channel, title :: !T.Text, startTime :: !T.Text, summary :: !T.Text } deriving (Eq, Show)
That did not help.
Then I tried deepseq:
instance NFData TvShow
return $!! result
That did not help.
And here's the catch: doing BOTH helps... I mean I think I'll check it again because I find it hard to believe but right now it really seems it behaves like that...
Is that possible? That I need to combine BOTH deepseq and bang patterns to actually get my code to evaluate when filling in the data? Or am I going crazy?
Thank you!
Emmanuel

On Dienstag, 25. Dezember 2012, 13:20:54, Emmanuel Touzery wrote:
to be clear: I definitely have strict evaluation now. It works. And it helped me to fix my bug (it's fixed now).
But I think that to actually get strict evaluation I needed BOTH bang patterns AND deep seq, at that same time... Which seems strange to me, I would think that either would suffice.
You need a bit less than what you (seem to) have. First, though, {-# LANGUAGE BangPatterns #-} data TvShow = TvShow { channel :: Channel, title :: !T.Text, startTime :: !T.Text, summary :: !T.Text } deriving (Eq, Show) the `!'s here are not bang patterns, they are strictness annotations on fields, and supported without extensions (Haskell2010, Haskell98, and presumably also earlier versions). Defining TvShow with strict fields for title, startTime and summary makes sure these fields are evaluated (to WHNF, but in case of `Data.Text`, that means fully evaluated) **when the TvShow value is evaluated to WHNF**. But when the value isn't evaluated, as in do ... let result = someFunction some arguments return result result remains a thunk, and thus its fields are not evaluated, even if marked strict. A simple return $! result to force evaluation of result to WHNF suffices to require the fields (except the `channel' field that's not marked strict) being evaluated. instance NFData TvShow that means you make TvShow an instance using the default implementation of `rnf', which is rnf a = a `seq` () In other words, with that instance, deepseq is exactly the same as seq for TvShow values, and ($!!) the same as ($!). Neither involves any of the fields. So what you have is exactly the same as strict fields + strict return (`return $! result'), although it looks like it would do more. The `return $!! result' alone (or `return $! result') without strictness annotations on the fields evaluates only the top-level constructor, TvShow. An NFData instance that would force the fields, instance NFData TvShow where rnf (TvShow c t st su) = c `seq` t `seq` st `seq` su `seq` () (that one involves the `channel', you can leave that out to get the behaviour you have now) with a return $!! result would achieve the evaluation without strictness annotations on the fields.

Thank you. I think you are as clear as possible, and complete.
I do wonder though, isn't there an annotation or technique that would force
the parameters of a constructor to be evaluated to WHNF when the
constructor is evaluated? In my case i believe the constructor is evaluated
immediately because it's in a do block of the IO monad.
I thought that's what the strictness annotations on the data members meant.
Thank you!
Emmanuel
On 25 Dec 2012 15:39, "Daniel Fischer"
On Dienstag, 25. Dezember 2012, 13:20:54, Emmanuel Touzery wrote:
to be clear: I definitely have strict evaluation now. It works. And it helped me to fix my bug (it's fixed now).
But I think that to actually get strict evaluation I needed BOTH bang patterns AND deep seq, at that same time... Which seems strange to me, I would think that either would suffice.
You need a bit less than what you (seem to) have.
First, though,
{-# LANGUAGE BangPatterns #-}
data TvShow = TvShow { channel :: Channel, title :: !T.Text, startTime :: !T.Text, summary :: !T.Text } deriving (Eq, Show)
the `!'s here are not bang patterns, they are strictness annotations on fields, and supported without extensions (Haskell2010, Haskell98, and presumably also earlier versions).
Defining TvShow with strict fields for title, startTime and summary makes sure these fields are evaluated (to WHNF, but in case of `Data.Text`, that means fully evaluated) **when the TvShow value is evaluated to WHNF**.
But when the value isn't evaluated, as in
do ... let result = someFunction some arguments return result
result remains a thunk, and thus its fields are not evaluated, even if marked strict.
A simple
return $! result
to force evaluation of result to WHNF suffices to require the fields (except the `channel' field that's not marked strict) being evaluated.
instance NFData TvShow
that means you make TvShow an instance using the default implementation of `rnf', which is
rnf a = a `seq` ()
In other words, with that instance, deepseq is exactly the same as seq for TvShow values, and ($!!) the same as ($!). Neither involves any of the fields.
So what you have is exactly the same as strict fields + strict return (`return $! result'), although it looks like it would do more.
The `return $!! result' alone (or `return $! result') without strictness annotations on the fields evaluates only the top-level constructor, TvShow.
An NFData instance that would force the fields,
instance NFData TvShow where rnf (TvShow c t st su) = c `seq` t `seq` st `seq` su `seq` ()
(that one involves the `channel', you can leave that out to get the behaviour you have now) with a
return $!! result
would achieve the evaluation without strictness annotations on the fields.

On Dienstag, 25. Dezember 2012, 19:07:33, Emmanuel Touzery wrote:
Thank you. I think you are as clear as possible, and complete. I do wonder though, isn't there an annotation or technique that would force the parameters of a constructor to be evaluated to WHNF when the constructor is evaluated?
That's what strictness annotations do.
In my case i believe the constructor is evaluated immediately because it's in a do block of the IO monad.
IO is still nonstrict in the values, data Strict = S !Int *Strict> do { putStrLn "Strictly"; return (S undefined); } Strictly *Strict> do { putStrLn "Strictly"; return $! (S undefined); } Strictly *** Exception: Prelude.undefined returning a value doesn't force its evaluation to WHNF.

A simple
return $! result
to force evaluation of result to WHNF suffices to require the fields (except the `channel' field that's not marked strict) being evaluated.
Otherwise I tested that right now and you are 100% right. So strictness annotations + $! works fine and solves my problem and I also mostly understand why it works like that :-) I still need to do a little more reading on the topic but I'm much closer now. Thank you! Emmanuel

On Tue, Dec 25, 2012 at 7:20 AM, Emmanuel Touzery
to be clear: I definitely have strict evaluation now. It works. And it helped me to fix my bug (it's fixed now).
But I think that to actually get strict evaluation I needed BOTH bang patterns AND deep seq, at that same time... Which seems strange to me, I would think that either would suffice.
Bang patterns / seq only evaluate to the first constructor; deepseq evaluates all the way down. It's not that surprising that you would need both, depending on what exactly you're doing. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
participants (3)
-
Brandon Allbery
-
Daniel Fischer
-
Emmanuel Touzery