<div dir="ltr"><div>I tried adding strictness to everything, forcing each line with "evaluate . force"<br><br></div>It still runs out of memory and now running with -hc blames the extra memory on "trace elements" which seems somewhat unhelpful.<br><br></div><div class="gmail_extra"><br><div class="gmail_quote">On Sat, Dec 13, 2014 at 2:10 PM, David Spies <span dir="ltr"><<a href="mailto:dnspies@gmail.com" target="_blank">dnspies@gmail.com</a>></span> wrote:<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div>I think there's some confusion about makeCounts's behavior.  makeCount never traverses the same thing twice.  Essentially, the worst-case size of the unevaluated thunks doesn't exceed the total size of the array of lists that was used to create them (and that array itself was created with accumArray which is strict).<br></div><div>Nonetheless, I've tried adding strictness all over makeCounts and it reduces the memory usage a little bit, but it still fails a later input instance with OOM.  It's not a significant reduction like in GHC 7.8.3<br><br></div></div><div class="HOEnZb"><div class="h5"><div class="gmail_extra"><br><div class="gmail_quote">On Sat, Dec 13, 2014 at 3:06 AM, Matthias Fischmann <span dir="ltr"><<a href="mailto:mf@zerobuzz.net" target="_blank">mf@zerobuzz.net</a>></span> wrote:<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><br>
Hi David,<br>
<br>
I don't think this is a ghc issue.<br>
<br>
I suspect you have too many unevaluated function calls lying around<br>
(this would cause the runtime to run out of *stack* as opposed to<br>
*heap*).  Different versions of ghc perform different optimizations on<br>
your code, and 7.8 knows a way to fix it that 7.6 doesn't know.<br>
<br>
This is usually solved by adding strictness: Instead of letting the<br>
unevaluated function calls pile up, you force them (e.g. with `print`<br>
or `Control.DeepSeq.deepseq`).<br>
<br>
I would take a closer look at your makeCounts function: you call<br>
traverse the input list, and traverse the entire list (starting from<br>
each element) again in each round.  Either you should find a way to<br>
iterate only once and accumulate all the data you need, or you should<br>
start optimizing there.<br>
<br>
hope this helps,<br>
cheers,<br>
matthias<br>
<br>
<br>
On Sat, Dec 13, 2014 at 02:06:52AM -0700, David Spies wrote:<br>
> Date: Sat, 13 Dec 2014 02:06:52 -0700<br>
> From: David Spies <<a href="mailto:dnspies@gmail.com" target="_blank">dnspies@gmail.com</a>><br>
> To: "<a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a>" <<a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a>><br>
> Subject: Program runs out of memory using GHC 7.6.3<br>
<div><div>><br>
> I have a program I submitted for a Kattis problem:<br>
> <a href="https://open.kattis.com/problems/digicomp2" target="_blank">https://open.kattis.com/problems/digicomp2</a><br>
> But I got memory limit exceeded.  I downloaded the test data and ran the<br>
> program on my own computer without problems.  Eventually I found out that<br>
> when compiling with GHC 7.6.3 (the version Kattis uses) rather than 7.8.3,<br>
> this program runs out of memory.<br>
> Can someone explain why it only works on the later compiler?  Is there a<br>
> workaround so that I can submit to Kattis?<br>
><br>
> Thanks,<br>
> David<br>
<br>
</div></div>> module Main(main) where<br>
><br>
> import           Control.Monad<br>
> import           Data.Array<br>
> import qualified Data.ByteString.Char8 as BS<br>
> import           Data.Int<br>
> import           Data.Maybe<br>
><br>
> readAsInt :: BS.ByteString -> Int<br>
> readAsInt = fst . fromJust . BS.readInt<br>
><br>
> readVert :: IO Vert<br>
> readVert = do<br>
>   [s, sl, sr] <- liftM BS.words BS.getLine<br>
>   return $ V (fromBS s) (readAsInt sl) (readAsInt sr)<br>
><br>
> main::IO()<br>
> main = do<br>
>   [n, m64] <- liftM (map read . words) getLine :: IO [Int64]<br>
>   let m = fromIntegral m64 :: Int<br>
>   verts <- replicateM m readVert<br>
>   let vside = map getSide verts<br>
>   let vpar = concat $ zipWith makeAssoc [1..] verts<br>
>   let parArr = accumArray (flip (:)) [] (1, m) vpar<br>
>   let counts = makeCounts n m $ elems parArr<br>
>   let res = zipWith doFlips counts vside<br>
>   putStrLn $ map toChar res<br>
><br>
> doFlips :: Int64 -> Side -> Side<br>
> doFlips n<br>
>   | odd n = flipSide<br>
>   | otherwise = id<br>
><br>
> makeCounts :: Int64 -> Int -> [[(Int, Round)]] -> [Int64]<br>
> makeCounts n m l = tail $ elems res<br>
>   where<br>
>     res = listArray (0, m) $ 0 : n : map makeCount (tail l)<br>
>     makeCount :: [(Int, Round)] -> Int64<br>
>     makeCount = sum . map countFor<br>
>     countFor :: (Int, Round) -> Int64<br>
>     countFor (i, Up) = ((res ! i) + 1) `quot` 2<br>
>     countFor (i, Down) = (res ! i) `quot` 2<br>
><br>
> fromBS :: BS.ByteString -> Side<br>
> fromBS = fromChar . BS.head<br>
><br>
> fromChar :: Char -> Side<br>
> fromChar 'L' = L<br>
> fromChar 'R' = R<br>
> fromChar _ = error "Bad char"<br>
><br>
> toChar :: Side -> Char<br>
> toChar L = 'L'<br>
> toChar R = 'R'<br>
><br>
> makeAssoc :: Int -> Vert -> [(Int, (Int, Round))]<br>
> makeAssoc n (V L a b) = filtPos [(a, (n, Up)), (b, (n, Down))]<br>
> makeAssoc n (V R a b) = filtPos [(a, (n, Down)), (b, (n, Up))]<br>
><br>
> filtPos :: [(Int, a)] -> [(Int, a)]<br>
> filtPos = filter ((> 0) . fst)<br>
><br>
> data Vert = V !Side !Int !Int<br>
><br>
> getSide :: Vert -> Side<br>
> getSide (V s _ _) = s<br>
><br>
> data Side = L | R<br>
><br>
> data Round = Up | Down<br>
><br>
> flipSide :: Side -> Side<br>
> flipSide L = R<br>
> flipSide R = L<br>
<div><div><br>
<br>
> _______________________________________________<br>
> ghc-devs mailing list<br>
> <a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a><br>
> <a href="http://www.haskell.org/mailman/listinfo/ghc-devs" target="_blank">http://www.haskell.org/mailman/listinfo/ghc-devs</a><br>
</div></div></blockquote></div></div>
</div></div></blockquote></div></div>