Hello everyone,
I've been running into the following error:
Reproduction.exe: getMBlocks: VirtualAlloc MEM_RESERVE 1 blocks
failed: Not enough storage is available to process this command.
The confusing part to me is that when the error occurs, Task Manager
reports that the process is using around 100K of memory, while I know
that the machine has at least 2GB available.
Reproduction case is attached. This runs against the Netflix prize
training set, which is large enough that I haven't attached it. At
the time that the error occurs, it's processed on the order of 15,500
files. Is it possible there's some other resource that I'm exhausting
without realizing it?
The compiler command line is:
ghc --make -O2 -threaded -hidir obj -odir obj -o Reproduction Reproduction.hs
/g
module Main where
import Control.Arrow
import Control.Monad (foldM)
import Control.Parallel.Strategies (rnf)
import qualified Data.ByteString.Char8 as B
import qualified Data.IntMap as M
import Data.List (foldl')
import System.Directory
import System.Environment (getArgs)
import System.IO (stderr, hPutStr)
loadMovie :: String -> IO (Maybe (Int, M.IntMap Int))
loadMovie path =
do text <- B.readFile path
return $
case B.lines text of
[] -> Nothing
(s:ss) ->
let Just (movie, _) = B.readInt s
in Just (movie, ratings ss)
where addInt list string = (movie, rating) : list
where Just (movie, rest) = B.readInt string
Just (rating, _) = B.readInt (B.tail rest)
ratings ss = rnf l `seq` M.fromList l
where l = foldl' addInt [] ss
load :: String -> IO (M.IntMap (M.IntMap Int))
load path =
do files <- getDirectoryContents path
case files of
[] -> return M.empty
_ -> foldM addMovie M.empty files
where addMovie :: M.IntMap (M.IntMap Int) -> String -> IO (M.IntMap (M.IntMap Int))
addMovie map file =
if file == "." || file == ".."
then return map
else do Just (movie, ratings) <- loadMovie (path ++ "\\" ++ file)
hPutStr stderr "."
return $ M.insert movie ratings map
averages path =
do movies <- load path
let averages = map (\(movie, ratings) -> (movie, M.fold (\rating (sum, count) -> (sum + rating, count + 1)) (0,0) ratings)) (M.toList movies)
averages' = map (second (\(sum, length) -> fromIntegral sum / fromIntegral length)) averages
mapM_ print averages'
main =
do args <- getArgs
averages (args !! 0)
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users