Re: [Haskell-cafe] serializing large data structures, stack overflow

2009-03-07 Thread Bulat Ziganshin
Hello friggin,

Saturday, March 7, 2009, 10:57:04 PM, you wrote:

> dec = B.decodeFile "C:/users/saftarn/desktop/bintest.txt" >>= \a ->
>    return $ (a :: M.Map (Int,Int) Int)

just a quick style hack:

dec = B.decodeFile "C:/users/saftarn/desktop/bintest.txt" :: IO (M.Map 
(Int,Int) Int)

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] serializing large data structures, stack overflow

2009-03-07 Thread Don Stewart

import Data.Binary and then write a variant of something like how
Maps are currently serialised:

instance (Ord k, Binary k, Binary e) => Binary (Map.Map k e) where
put m = put (Map.size m) >> mapM_ put (Map.toAscList m)
get   = liftM Map.fromDistinctAscList get

So you might want something that avoids flattening it to a list first

-- Don

frigginfriggins:
> can you link to a good example of writing your own because I couldn't find 
> one.
> 
> On Sat, Mar 7, 2009 at 8:57 PM, Don Stewart  wrote:
> 
> Increase the stack size, or use a different serialiser (they're only a
> half dozen lines to write), or different data structure?
> 
> -- Don
> 
> frigginfriggins:
> > I'm playing around with Netflix, implementing a simple KNN-algorithm, I
> will
> > later try SVD which seems to be the most successful approach.
> >
> > Using a database like Postgresqk is to slow so I want to serialize a
> > datastructure containing the ratings. I'm not sure about the
> > representation I will use just yet, if I should use multiple arrays or 
> an
> Map/
> > IntMap.
> >
> > However I tried Data.Binary and already for small sizes I get stack
> overflow
> > when deserializing.
> > The serializing works fine but when bringing it back it overflows.
> > How can I solve this? This is just 2MB, I will eventually need soemthing
> like
> > 2-500MB to store everything depending on what representatin I choose.
> >
> > module Serialize where
> > import qualified Data.Binary as B
> > import qualified Data.Binary.Put as P
> > import qualified Data.Map as M
> > import qualified Data.List as L
> >
> > genTest :: Int -> M.Map (Int,Int) Int
> > genTest n = let movies = take n $ repeat 1
> > grades = take n $ repeat 4 in
> > M.fromList $ ([1..n] `zip` movies) `zip` grades
> >
> > main = do
> >   let a = genTest 5
> >   B.encodeFile "C:/users/saftarn/desktop/bintest.txt" a
> >   print "Success"
> >
> > dec = B.decodeFile "C:/users/saftarn/desktop/bintest.txt" >>= \a ->
> >   return $ (a :: M.Map (Int,Int) Int)
> >
> >
> >
> >
> 
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
> 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] serializing large data structures, stack overflow

2009-03-07 Thread Don Stewart
Increase the stack size, or use a different serialiser (they're only a
half dozen lines to write), or different data structure?

-- Don

frigginfriggins:
> I'm playing around with Netflix, implementing a simple KNN-algorithm, I will
> later try SVD which seems to be the most successful approach.
> 
> Using a database like Postgresqk is to slow so I want to serialize a
> datastructure containing the ratings. I'm not sure about the
> representation I will use just yet, if I should use multiple arrays or an Map/
> IntMap.
> 
> However I tried Data.Binary and already for small sizes I get stack overflow
> when deserializing.
> The serializing works fine but when bringing it back it overflows.
> How can I solve this? This is just 2MB, I will eventually need soemthing like
> 2-500MB to store everything depending on what representatin I choose.
> 
> module Serialize where
> import qualified Data.Binary as B
> import qualified Data.Binary.Put as P
> import qualified Data.Map as M
> import qualified Data.List as L
> 
> genTest :: Int -> M.Map (Int,Int) Int
> genTest n = let movies = take n $ repeat 1
> grades = take n $ repeat 4 in
> M.fromList $ ([1..n] `zip` movies) `zip` grades
> 
> main = do
>   let a = genTest 5
>   B.encodeFile "C:/users/saftarn/desktop/bintest.txt" a
>   print "Success"
> 
> dec = B.decodeFile "C:/users/saftarn/desktop/bintest.txt" >>= \a ->
>   return $ (a :: M.Map (Int,Int) Int)
> 
> 
> 
> 

> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] serializing large data structures, stack overflow

2009-03-07 Thread friggin friggin
I'm playing around with Netflix, implementing a simple KNN-algorithm, I will
later try SVD which seems to be the most successful approach.

Using a database like Postgresqk is to slow so I want to serialize a
datastructure containing the ratings. I'm not sure about the
representation I will use just yet, if I should use multiple arrays or an
Map/IntMap.

However I tried Data.Binary and already for small sizes I get stack overflow
when deserializing.
The serializing works fine but when bringing it back it overflows.
How can I solve this? This is just 2MB, I will eventually need soemthing
like 2-500MB to store everything depending on what representatin I choose.

module Serialize where
import qualified Data.Binary as B
import qualified Data.Binary.Put as P
import qualified Data.Map as M
import qualified Data.List as L

genTest :: Int -> M.Map (Int,Int) Int
genTest n = let movies = take n $ repeat 1
grades = take n $ repeat 4 in
M.fromList $ ([1..n] `zip` movies) `zip` grades

main = do
  let a = genTest 5
  B.encodeFile "C:/users/saftarn/desktop/bintest.txt" a
  print "Success"

dec = B.decodeFile "C:/users/saftarn/desktop/bintest.txt" >>= \a ->
  return $ (a :: M.Map (Int,Int) Int)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe