
Would it be possible to bring the DeepSeq library into the libraries distributed with GHC? (I think Dean Herington is responsible for it.) Of course it's easy enough to drop it into one's own program (I am just about to do this) but (1) It is fairly common to want to force deeper evaluation. (2) DeepSeq is simple enough to be dropped in the GHC distribution, without it causing much trouble or making it much bigger. (3) At the same time, it is not so simple that it can be reimplemented in a couple of lines.

On Friday 19 July 2002 12:10, George Russell wrote:
Would it be possible to bring the DeepSeq library into the libraries distributed with GHC? (I think Dean Herington is responsible for it.)
Of course it's easy enough to drop it into one's own program (I am just about to do this) but (1) It is fairly common to want to force deeper evaluation. (2) DeepSeq is simple enough to be dropped in the GHC distribution, without it causing much trouble or making it much bigger. (3) At the same time, it is not so simple that it can be reimplemented in a couple of lines.
Agree. Beeing able to derive instances of DeepSeq would be nice too. J.A.

Beeing able to derive instances of DeepSeq would be nice too.
Here is an implementation using GHC's derivable type classes. Cheers, Ralf ---- ghc -c -fglasgow-exts -fgenerics -package lang Eval.lhs
module Force where import Generics
class Force a where force :: a -> ()
force{|Unit|} a = a `seq` ()
force{|b :+: c|} a = case a of Inl b -> force b Inr c -> force c
force{|b :*: c|} a = case a of b :*: c -> force b `seq` force c
instance Force Char where force a = a `seq` () instance Force Int where force a = a `seq` ()
eval :: (Force a) => a -> a eval a = force a `s

DrIFT can derive 'rnf' or reduce to normal form for arbitrary classes which is similar to deepSeq, in fact does anyone have a good description as to how they are different? John On Fri, Jul 19, 2002 at 12:31:40PM +0100, Jorge Adriano wrote:
On Friday 19 July 2002 12:10, George Russell wrote:
Would it be possible to bring the DeepSeq library into the libraries distributed with GHC? (I think Dean Herington is responsible for it.)
Of course it's easy enough to drop it into one's own program (I am just about to do this) but (1) It is fairly common to want to force deeper evaluation. (2) DeepSeq is simple enough to be dropped in the GHC distribution, without it causing much trouble or making it much bigger. (3) At the same time, it is not so simple that it can be reimplemented in a couple of lines.
Agree. Beeing able to derive instances of DeepSeq would be nice too.
J.A. _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- --------------------------------------------------------------------------- John Meacham - California Institute of Technology, Alum. - john@foo.net ---------------------------------------------------------------------------
participants (4)
-
George Russell
-
John Meacham
-
Jorge Adriano
-
Ralf Hinze