
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.