Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Restoring interleaved lists? (Felipe Lessa)
   2. Re:  Restoring interleaved lists? (Henk-Jan van Tuyl)
   3. Re:  Profiling introduces a space leak where      there was none
      before? (Brent Yorgey)
   4. Re:  Profiling introduces a space leak where there        was none
      before? (Daniel Fischer)


----------------------------------------------------------------------

Message: 1
Date: Thu, 12 Aug 2010 22:23:13 -0300
From: Felipe Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] Restoring interleaved lists?
To: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Cc: beginners <beginners@haskell.org>
Message-ID:
        <aanlkti=e6rjsbhahjlpmkq=hgvureyrmyw-tm-vht...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Thu, Aug 12, 2010 at 10:11 PM, Patrick LeBoutillier
<patrick.leboutill...@gmail.com> wrote:
> I need a function that, given t and the list of t*m measures, can
> spilt the measures by track, returning a list of t lists, each
> containing m measures. I cannot figure out how to do this, even though
> it seems to me like it shouldn't be too hard... I can't figure out how
> to "update" the lists of lists when I want to add a new element.
>
> Do anyone have any ideas?

I won't post the complete code and will just throw ideas around,
please let us know if you still get stuck =).

We have the following function in the Prelude:

  splitAt :: Int -> [a] -> ([a], [a])

For example,

  Prelude> splitAt 3 [1..12]
  ([1,2,3],[4,5,6,7,8,9,10,11,12])

So you can write the following function (you can choose another name):

  separate :: Int -> [a] -> [[a]]

For example,

  Prelude> separate 3 [1..12]
  [[1,2,3],[4,5,6],[7,8,9],[10,11,12]]

But that's not what we wanted.  Hmmm, from Data.List we have

  transpose :: [[a]] -> [[a]]

For example:

  Prelude Data.List> transpose [[1,2,3],[4,5,6],[7,8,9],[10,11,12]]
  [[1,4,7,10],[2,5,8,11],[3,6,9,12]]

Bingo!

Hope that helps ;-),

-- 
Felipe.


------------------------------

Message: 2
Date: Fri, 13 Aug 2010 11:44:10 +0200
From: "Henk-Jan van Tuyl" <hjgt...@chello.nl>
Subject: Re: [Haskell-beginners] Restoring interleaved lists?
To: "Patrick LeBoutillier" <patrick.leboutill...@gmail.com>,    "Felipe
        Lessa" <felipe.le...@gmail.com>
Cc: beginners <beginners@haskell.org>
Message-ID: <op.vhdenwdppz0...@zen5.router.home>
Content-Type: text/plain; charset=iso-8859-15; format=flowed;
        delsp=yes

On Fri, 13 Aug 2010 03:23:13 +0200, Felipe Lessa <felipe.le...@gmail.com>  
wrote:

>
> We have the following function in the Prelude:
>
>   splitAt :: Int -> [a] -> ([a], [a])
>
> For example,
>
>   Prelude> splitAt 3 [1..12]
>   ([1,2,3],[4,5,6,7,8,9,10,11,12])
>
> So you can write the following function (you can choose another name):
>
>   separate :: Int -> [a] -> [[a]]
>
> For example,
>
>   Prelude> separate 3 [1..12]
>   [[1,2,3],[4,5,6],[7,8,9],[10,11,12]]
>

This is the splitEvery function of package split; you can find this with  
Hayoo, using the word "split".

Regards,
Henk-Jan van Tuyl


-- 
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
--


------------------------------

Message: 3
Date: Fri, 13 Aug 2010 13:59:07 +0100
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Profiling introduces a space leak
        where   there was none before?
To: beginners@haskell.org
Message-ID: <20100813125907.ga31...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

I suggest that you send this message to the haskell-c...@haskell.org
mailing list.  Not that it isn't welcome here, but answering it
requires fairly specialised knowledge (I at least have no idea what
the answer is) and you'll probably get better help there.

-Brent

On Thu, Aug 12, 2010 at 06:20:49PM -0700, Travis Erdman wrote:
> In Ch 25 of Real World Haskell, the authors introduce some naive code for 
> finding the average of a big list; it has a space leak, and they present 
> several 
> solutions.  
> 
> 
> Below are two of the solutions that successfully eliminate the space leak 
> (though, the first one -- the one that uses foldl'rnf -- is quite a bit 
> faster).   However, if compiled with profiling, the first one (using 
> foldl'rnf) 
> NOW has a leak.  The second solution (foldl') does not have a leak even when 
> profiling is enabled.
> 
> I have used this foldl'rnf function in my own code, as it is the only 
> solution I 
> have found for a space leak in my own code.  But, since it leaks when 
> profiled, 
> it is making analysis difficult.
> 
> Is this a feature, bug, or user error?  If a known issue, is there a 
> workaround?  The code and some documenting output follows.
> 
> thanks,
> 
> Travis
> ------------------------------------
> 
> {-# LANGUAGE BangPatterns #-}
> 
> import System.Environment
> import Text.Printf
> import Control.Parallel.Strategies
> import Control.DeepSeq
> import Data.List (foldl')
> 
> main = do
>     [d] <- map read `fmap` getArgs
>     printf "%f\n" (mean [1..d])
> 
> foldl'rnf :: NFData a => (a -> b -> a) -> a -> [b] -> a
> foldl'rnf f z xs = lgo z xs
>     where
>         lgo z []     = z
>         lgo z (x:xs) = lgo z' xs
>             where
>                 z' = f z x `using` rdeepseq
> 
> -- first mean fn aka foldl'rnf
> mean :: [Double] -> Double
> mean xs = s / fromIntegral n
>   where
>     (n, s)     = foldl'rnf k (0, 0) xs
>     k (n, s) x = (n+1, s+x) :: (Int, Double)
> 
> -- second mean fn aka foldl'    
> -- mean :: [Double] -> Double
> -- mean xs = s / fromIntegral n
>   -- where
>     -- (n, s)       = foldl' k (0, 0) xs
>     -- k (!n, !s) x = (n+1, s+x)
> 
> ------------------------------------------
> 
> [NO PROFILING, NO SPACE LEAK]
> 
> C:\Documents and Settings\Travis\My Documents\Haskell Code>ghc --make temp5 
> -O2 
> -fasm
> [1 of 1] Compiling Main             ( temp5.hs, temp5.o )
> Linking temp5.exe ...
> 
> C:\Documents and Settings\Travis\My Documents\Haskell Code>temp5 1e7 +RTS 
> -sstderr
> temp5 1e7 +RTS -sstderr
> 5000000.5
>    1,170,230,652 bytes allocated in the heap
>          128,876 bytes copied during GC
>            3,372 bytes maximum residency (1 sample(s))
>           13,012 bytes maximum slop
>                1 MB total memory in use (0 MB lost due to fragmentation)
> 
>   Generation 0:  2232 collections,     0 parallel,  0.05s,  0.05s elapsed
>   Generation 1:     1 collections,     0 parallel,  0.00s,  0.00s elapsed
> 
>   INIT  time    0.02s  (  0.03s elapsed)
>   MUT   time    1.52s  (  1.55s elapsed)
>   GC    time    0.05s  (  0.05s elapsed)
>   EXIT  time    0.00s  (  0.00s elapsed)
>   Total time    1.58s  (  1.63s elapsed)
> 
>   %GC time       3.0%  (2.9% elapsed)
> 
>   Alloc rate    764,232,262 bytes per MUT second
> 
>   Productivity  96.0% of total user, 93.3% of total elapsed
> 
> 
> C:\Documents and Settings\Travis\My Documents\Haskell Code>temp5 1e8 +RTS 
> -sstderr
> temp5 1e8 +RTS -sstderr
> 50000000.5
>   11,702,079,228 bytes allocated in the heap
>        1,253,872 bytes copied during GC
>            3,372 bytes maximum residency (1 sample(s))
>           13,012 bytes maximum slop
>                1 MB total memory in use (0 MB lost due to fragmentation)
> 
>   Generation 0: 22321 collections,     0 parallel,  0.38s,  0.39s elapsed
>   Generation 1:     1 collections,     0 parallel,  0.00s,  0.00s elapsed
> 
>   INIT  time    0.02s  (  0.00s elapsed)
>   MUT   time   15.47s  ( 15.72s elapsed)
>   GC    time    0.38s  (  0.39s elapsed)
>   EXIT  time    0.00s  (  0.00s elapsed)
>   Total time   15.86s  ( 16.11s elapsed)
> 
>   %GC time       2.4%  (2.4% elapsed)
> 
>   Alloc rate    755,734,682 bytes per MUT second
> 
>   Productivity  97.5% of total user, 96.0% of total elapsed
> 
> 
> 
> [NOW TURN ON PROFILING, GET SPACE LEAK]
> 
> C:\Documents and Settings\Travis\My Documents\Haskell Code>ghc --make temp5 
> -O2 
> -fasm -prof -auto-all
> [1 of 1] Compiling Main             ( temp5.hs, temp5.o )
> Linking temp5.exe ...
> 
> C:\Documents and Settings\Travis\My Documents\Haskell Code>temp5 1e6 +RTS 
> -sstderr -p -K128M
> temp5 1e6 +RTS -sstderr -p -K128M
> 500000.5
>      395,774,976 bytes allocated in the heap
>      238,684,620 bytes copied during GC
>      102,906,760 bytes maximum residency (7 sample(s))
>       66,283,900 bytes maximum slop
>              179 MB total memory in use (4 MB lost due to fragmentation)
> 
>   Generation 0:   493 collections,     0 parallel,  4.83s,  4.84s elapsed
>   Generation 1:     7 collections,     0 parallel,  0.23s,  0.30s elapsed
> 
>   INIT  time    0.02s  (  0.03s elapsed)
>   MUT   time    0.81s  (  0.91s elapsed)
>   GC    time    5.06s  (  5.14s elapsed)
>   RP    time    0.00s  (  0.00s elapsed)
>   PROF  time    0.00s  (  0.00s elapsed)
>   EXIT  time    0.00s  (  0.00s elapsed)
>   Total time    5.89s  (  6.08s elapsed)
> 
>   %GC time      85.9%  (84.6% elapsed)
> 
>   Alloc rate    477,916,952 bytes per MUT second
> 
>   Productivity  13.8% of total user, 13.4% of total elapsed
> 
> 
>       
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


------------------------------

Message: 4
Date: Fri, 13 Aug 2010 15:41:52 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Profiling introduces a space leak
        where there     was none before?
To: beginners@haskell.org
Cc: Travis Erdman <traviserd...@yahoo.com>
Message-ID: <201008131541.53070.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Friday 13 August 2010 03:20:49, Travis Erdman wrote:
> In Ch 25 of Real World Haskell, the authors introduce some naive code
> for finding the average of a big list; it has a space leak, and they
> present several solutions.
>
>
> Below are two of the solutions that successfully eliminate the space
> leak (though, the first one -- the one that uses foldl'rnf -- is quite a
> bit faster).   However, if compiled with profiling, the first one (using
> foldl'rnf) NOW has a leak.  The second solution (foldl') does not have a
> leak even when profiling is enabled.
>
> I have used this foldl'rnf function in my own code, as it is the only
> solution I have found for a space leak in my own code.  But, since it
> leaks when profiled, it is making analysis difficult.
>
> Is this a feature, bug, or user error?  If a known issue, is there a
> workaround?  The code and some documenting output follows.

I must admit I don't really understand what's going on.
However, compiling for profiling makes some optimisations impossible, so 
different behaviour between profiling and non-profiling code isn't too 
surprising.
Since the profiling version overflows the default stack, it seems to be a 
problem of missing strictness.
I believe, what happens is that profiling prevents too much inlining, so 
that the strictness analyser gets confused.

>
> thanks,
>
> Travis
> ------------------------------------
>
> {-# LANGUAGE BangPatterns #-}
>
> import System.Environment
> import Text.Printf
> import Control.Parallel.Strategies
> import Control.DeepSeq
> import Data.List (foldl')
>
> main = do
>     [d] <- map read `fmap` getArgs
>     printf "%f\n" (mean [1..d])
>
> foldl'rnf :: NFData a => (a -> b -> a) -> a -> [b] -> a
> foldl'rnf f z xs = lgo z xs
>     where
>         lgo z []     = z
>         lgo z (x:xs) = lgo z' xs
>             where
>                 z' = f z x `using` rdeepseq

You get better Core and a faster mean with

     lgo z (x:xs) = let z' = f z x in deepseq z' (lgo z' xs)

as the second equation. Alas, that doesn't fix the profiling space-leak.
For fixing the space leak, it is important whether the fold is defined in a 
library module and compiled separately or, as is the case here, it's 
defined in the Main module and not exported.
There are several variants that fix the leak in the latter setting but not 
in the former.

Since the former is the interesting case (in the latter case you can write 
faster specialised code), the version that fixes the profiling space leak 
as a separately compiled library function (at least, there's no leak here):


noleak :: NFData a => (a -> b -> a) -> a -> [b] -> a
noleak f = nol
  where
    nol !z [] = z
    nol z (x:xs) = case rdeepseq (f z x) of
                    Done z' -> nol z' xs

The important points are
- manually inlining `using` in some way
- the bang on z in the first equation (would probably also work with a bang 
in the second equation instead of the first)

The above gives however a spurious deprecation warning (the warning code 
confuses the data constructor Done of data Eval with the deprecated type 
alias type Done = (), so it warns). To avoid that, you can also write the 
second equation as

    nol z (x:xs) = nol (runEval (rdeepseq (f z x))) xs

Non-profiling performance is, as far as I can tell, identical to that of 
your foldl'rnf.



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 26, Issue 29
*****************************************

Reply via email to