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

-- 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

What is the error that you get?
Cheers,
Pedro
On Tue, Apr 16, 2013 at 8:07 PM, Anatoly Yakovenko
-- 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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
What is the error that you get?
Cheers, Pedro
On Tue, Apr 16, 2013 at 8:07 PM, Anatoly Yakovenko
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

-- + Roman,
-- hey Roman,
-- seems like i cant use deepseq or Generic derive of NFData on data types
containing vectors. The following code tries to use deepseq to force
evaluation of a type containing vectors, but when the code is running it
seems to not work as expected (blows up in memory). any ideas?
{-# 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
On Tue, Apr 16, 2013 at 12:36 PM, anatoly yakovenko
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
wrote: What is the error that you get?
Cheers, Pedro
On Tue, Apr 16, 2013 at 8:07 PM, Anatoly Yakovenko < aeyakovenko@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Anatoly. I don't think that the normal deepseq package currently provides generic deriving at all. This doesn't have anything to do with vector. There's a default implementation for rnf that defines it to be seq, which is not what you want in this case, of course. There are additional packages that implement such functionality, though. By using deepseq-generics, you can import Control.DeepSeq.Generics and then define
instance NFData Simple where rnf = genericRnf
Cheers, Andres -- Andres Löh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com

Thanks, So now i at least get a compiler error
No instance for (NFData (V.Vector Double))
So how would one define NFData instance for vector?
On Apr 16, 2013, at 10:51 PM, Andres Löh
NFData Simple where rnf = genericRnf

so this one works
instance NFData (V.Vector a) where rnf a = force a `seq` ()
any reason why something like this isn't part of the vector library?
Thanks,
Anatoly
On Apr 17, 2013, at 7:51 AM, anatoly yakovenko
Thanks, So now i at least get a compiler error
No instance for (NFData (V.Vector Double))
So how would one define NFData instance for vector?
On Apr 16, 2013, at 10:51 PM, Andres Löh
wrote: NFData Simple where rnf = genericRnf

Hi again.
instance NFData (V.Vector a) where rnf a = force a `seq` ()
any reason why something like this isn't part of the vector library?
Quoting from the Changelog at http://hackage.haskell.org/package/vector : " Changes in version 0.10 * NFData instances " So it's there, and even in the current Haskell Platform. Cheers, Andres -- Andres Löh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com
participants (4)
-
anatoly yakovenko
-
Anatoly Yakovenko
-
Andres Löh
-
José Pedro Magalhães