Hello Justin,<br><br>I tried and what I saw was a constant increase in memory usage.<br>Any particular profiling option that you would use?<br><br>I do remember that there was a particular option in which the leak would dissapear (for the same amount of work) and that is why I stopped using the profiler.<br>
<br>Thanks,<br><br>Arnoldo<br><br><br><div class="gmail_quote">On Wed, Mar 10, 2010 at 10:20 PM, Justin Bailey <span dir="ltr">&lt;<a href="mailto:jgbailey@gmail.com">jgbailey@gmail.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">
Have you use the profiling tools available with GHC?<br>
<br>
  <a href="http://haskell.org/ghc/docs/latest/html/users_guide/profiling.html" target="_blank">http://haskell.org/ghc/docs/latest/html/users_guide/profiling.html</a><br>
<div><div></div><div class="h5"><br>
<br>
On Wed, Mar 10, 2010 at 12:45 PM, Arnoldo Muller<br>
&lt;<a href="mailto:arnoldomuller@gmail.com">arnoldomuller@gmail.com</a>&gt; wrote:<br>
&gt; Hello,<br>
&gt;<br>
&gt; I am learning haskell and I found a space leak that I find difficult to<br>
&gt; solve. I&#39;ve been asking at #haskell but we could not solve<br>
&gt; the issue.<br>
&gt;<br>
&gt; I want to lazily read a set of 22 files of about 200MB each, filter them and<br>
&gt; then I want to output the result into a unique file.<br>
&gt; If I modify the main function to work only with one input file,  the program<br>
&gt; runs without issues. I will call this version A.<br>
&gt; Version B  uses a mapM_ to iterate over a list of filenames and uses<br>
&gt; appendFile to output the result of filtering each file.<br>
&gt; In this case the memory usage grows sharply and quickly (profiles show<br>
&gt; constant memory growth). In less than a minute, memory<br>
&gt; occupation will make my system hang with swapping.<br>
&gt;<br>
&gt; This is version B:<br>
&gt;<br>
&gt; ------------------------------- Program B<br>
&gt; --------------------------------------------------------------------------------------------------------------------<br>
&gt; import Data.List<br>
&gt; import System.Environment<br>
&gt; import System.Directory<br>
&gt; import Control.Monad<br>
&gt;<br>
&gt;<br>
&gt; -- different types of chromosomes<br>
&gt; data Chromosome =    C1<br>
&gt;                 | C2<br>
&gt;                 | C3<br>
&gt;                 | C4<br>
&gt;                 | C5<br>
&gt;                 | C6<br>
&gt;                 | C7<br>
&gt;                 | C8<br>
&gt;                 | C9<br>
&gt;                 | C10<br>
&gt;                 | C11<br>
&gt;                 | C12<br>
&gt;                 | C13<br>
&gt;                 | C14<br>
&gt;                 | C15<br>
&gt;                 | C16<br>
&gt;                 | C17<br>
&gt;                 | C18<br>
&gt;                 | C19<br>
&gt;                 | CX<br>
&gt;                 | CY<br>
&gt;                 | CMT<br>
&gt;                   deriving (Show)<br>
&gt; -- define a window<br>
&gt; type Sequence = [Char]<br>
&gt; -- Window data<br>
&gt; data Window = Window { sequen :: Sequence,<br>
&gt;                        chrom :: Chromosome,<br>
&gt;                        pos   :: Int<br>
&gt;                      }<br>
&gt; -- print a window<br>
&gt; instance Show Window where<br>
&gt;     show w =  (sequen w) ++ &quot;\t&quot; ++ show (chrom w) ++ &quot;\t&quot; ++ show (pos w)<br>
&gt;<br>
&gt; -- Reading fasta files with haskell<br>
&gt;<br>
&gt; -- Initialize the<br>
&gt; main = do<br>
&gt;        -- get the arguments (intput is<br>
&gt;        [input, output, windowSize] &lt;- getArgs<br>
&gt;        -- get directory contents (only names)<br>
&gt;        names &lt;- getDirectoryContents input<br>
&gt;        -- prepend directory<br>
&gt;        let fullNames = filter isFastaFile $ map (\x -&gt; input ++ &quot;/&quot; ++ x)<br>
&gt; names<br>
&gt;        let wSize = (read windowSize)::Int<br>
&gt;        -- process the directories<br>
&gt;        mapM (genomeExecute output wSize filterWindow)  fullNames<br>
&gt;<br>
&gt;<br>
&gt; -- read the files one by one and write them to the output file<br>
&gt; genomeExecute :: String -&gt; Int -&gt; (Window -&gt; Bool) -&gt; String -&gt; IO ()<br>
&gt; genomeExecute  outputFile windowSize f inputFile = do<br>
&gt;   fileData &lt;- readFile inputFile<br>
&gt;   appendFile outputFile $ fastaExtractor fileData windowSize f<br>
&gt;<br>
&gt; --<br>
&gt; isFastaFile :: String -&gt; Bool<br>
&gt; isFastaFile fileName = isSuffixOf &quot;.fa&quot; fileName<br>
&gt;<br>
&gt;<br>
&gt; -- fasta extractor (receives a Fasta String and returns a windowed string<br>
&gt; ready to be sorted)<br>
&gt; -- an example on how to compose several functions to parse a fasta file<br>
&gt; fastaExtractor :: String -&gt; Int -&gt; (Window -&gt; Bool) -&gt; String<br>
&gt; fastaExtractor input wSize f = printWindowList $ filter f $ readFasta  wSize<br>
&gt; input<br>
&gt;<br>
&gt; -- MAIN FILTER that removes N elements from the strings!<br>
&gt; filterWindow :: Window -&gt; Bool<br>
&gt; filterWindow w = not (elem &#39;N&#39; (sequen w))<br>
&gt;<br>
&gt; -- print a window list (the printing makes it ready for output as raw data)<br>
&gt; printWindowList :: [Window] -&gt; String<br>
&gt; printWindowList l = unlines $ map show l<br>
&gt;<br>
&gt; -- read fasta, remove stuff that is not useful from it<br>
&gt; -- removes the<br>
&gt; readFasta :: Int -&gt; [Char] -&gt; [Window]<br>
&gt; readFasta windowSize sequence =<br>
&gt;     -- get the header<br>
&gt;     let (header:rest) = lines sequence<br>
&gt;         chr = parseChromosome header<br>
&gt;         in<br>
&gt;<br>
&gt; -- We now do the following:<br>
&gt; --      take window                  create counter<br>
&gt; remove newlines<br>
&gt;    map (\(i, w) -&gt; Window w chr i) $ zip [0..]  $ slideWindow windowSize  $<br>
&gt; filter ( &#39;\n&#39; /= )  $ unlines rest<br>
&gt;<br>
&gt;<br>
&gt; slideWindow :: Int -&gt; [Char] -&gt; [[Char]]<br>
&gt; slideWindow _ [] = []<br>
&gt; slideWindow windowSize l@(_:xs)  = take windowSize l : slideWindow<br>
&gt; windowSize xs<br>
&gt;<br>
&gt;<br>
&gt;<br>
&gt; -- Parse the chromosome from a fasta comment<br>
&gt; -- produce a more compact chromosome representation<br>
&gt; parseChromosome :: [Char] -&gt; Chromosome<br>
&gt; parseChromosome line<br>
&gt;     | isInfixOf &quot;chromosome 1,&quot; line = C1<br>
&gt;     | isInfixOf &quot;chromosome 2,&quot; line = C2<br>
&gt;     | isInfixOf &quot;chromosome 3,&quot; line = C3<br>
&gt;     | isInfixOf &quot;chromosome 4,&quot; line = C4<br>
&gt;     | isInfixOf &quot;chromosome 5,&quot; line = C5<br>
&gt;     | isInfixOf &quot;chromosome 6,&quot; line = C6<br>
&gt;     | isInfixOf &quot;chromosome 7,&quot; line = C7<br>
&gt;     | isInfixOf &quot;chromosome 8,&quot; line = C9<br>
&gt;     | isInfixOf &quot;chromosome 10,&quot; line = C10<br>
&gt;     | isInfixOf &quot;chromosome 11,&quot; line = C11<br>
&gt;     | isInfixOf &quot;chromosome 12,&quot; line = C12<br>
&gt;     | isInfixOf &quot;chromosome 13,&quot; line = C13<br>
&gt;     | isInfixOf &quot;chromosome 14,&quot; line = C14<br>
&gt;     | isInfixOf &quot;chromosome 15,&quot; line = C15<br>
&gt;     | isInfixOf &quot;chromosome 16,&quot; line = C16<br>
&gt;     | isInfixOf &quot;chromosome 17&quot;  line = C17<br>
&gt;     | isInfixOf &quot;chromosome 18&quot;  line = C18<br>
&gt;     | isInfixOf &quot;chromosome 19&quot;  line = C19<br>
&gt;     | isInfixOf &quot;chromosome X&quot;   line = CX<br>
&gt;     | isInfixOf &quot;chromosome Y&quot;   line = CY<br>
&gt;     | isInfixOf &quot;mitochondrion&quot;  line = CMT<br>
&gt;     | otherwise = error &quot;BAD header&quot;<br>
&gt;<br>
&gt;<br>
&gt; -------------------------------- End of program B<br>
&gt; ------------------------------------------------------------------------------------------------<br>
&gt;<br>
&gt; -------------------------------- Program A<br>
&gt; ---------------------------------------------------------------------------------------------------------<br>
&gt; If instead of the main function given above I use the following main<br>
&gt; function to process only one input file, things work OK for even<br>
&gt; the largest files. Memory usage remains constant in this case.<br>
&gt;<br>
&gt; main = do<br>
&gt;        -- get the arguments<br>
&gt;        [input, output, windowSize] &lt;- getArgs<br>
&gt;        -- keep the input stream<br>
&gt;        inpStr &lt;- readFile input<br>
&gt;        let wSize = (read windowSize)::Int<br>
&gt;        writeFile output $ fastaExtractor inpStr wSize filterWindow<br>
&gt;<br>
&gt;<br>
&gt; It is not easy for me to see why is Haskell keeping data in memory. Do you<br>
&gt; have any idea why  program B is<br>
&gt; not working?<br>
&gt;<br>
&gt; Thank you for your help!<br>
&gt;<br>
&gt; Arnoldo Muller<br>
&gt;<br>
</div></div>&gt; _______________________________________________<br>
&gt; Haskell-Cafe mailing list<br>
&gt; <a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
&gt; <a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
&gt;<br>
&gt;<br>
</blockquote></div><br>