[Haskell-cafe] Derving NFData via Generics from a type that has a vector doesn't work. (was trying to understand out of memory exceptions)

anatoly yakovenko aeyakovenko at gmail.com
Tue Apr 16 21:36:38 CEST 2013


This compiles but the process runs out of memory, so it seams that NFData derivation isn't doing its job.


On Apr 16, 2013, at 12:15 PM, José Pedro Magalhães <jpm at cs.uu.nl> wrote:

> What is the error that you get?
> 
> 
> Cheers,
> Pedro
> 
> On Tue, Apr 16, 2013 at 8:07 PM, Anatoly Yakovenko <aeyakovenko at gmail.com> wrote:
> -- ok, something in deriving NFData using Generics in a type that has a Vector in it.
> 
> 
> {-# LANGUAGE DeriveGeneric #-}
> import Control.DeepSeq
> import System.IO
> import GHC.Generics (Generic)
> import qualified Data.Vector as V
> import qualified Data.ByteString.Lazy.Char8 as BL
> 
> scanl' :: NFData a => (a -> b -> a) -> a -> [b] -> [a]
> scanl' f q ls =  q : (case ls of
>                         []   -> []
>                         x:xs -> let q' = f q x
>                                 in q' `deepseq` scanl' f q' xs)
> 
> -- this runs without blowing up
> -- main = print $ last $ scanl' (+) (0::Int) [0..]
> 
> data Simple = Simple (V.Vector Double)
>             deriving (Show, Generic)
> 
> instance NFData Simple
> 
> --this blows up
> main = do
>    let initial = Simple $ V.fromList (take 100 $ repeat 0)
>        sumvs (Simple a) (Simple b) = Simple $ V.zipWith (+) a b
>    print $ last $ scanl' sumvs initial $ repeat $ initial
> 
> 
> 
> _______________________________________________
> 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