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: ghci access to .hs functions (prad)
   2. Re:  Re: ghci access to .hs functions (MAN)
   3. Re:  Re: ghci access to .hs functions (Daniel Fischer)
   4.  Restoring interleaved lists? (Patrick LeBoutillier)
   5.  Profiling introduces a space leak where there    was none
      before? (Travis Erdman)


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

Message: 1
Date: Thu, 12 Aug 2010 13:18:11 -0700
From: prad <p...@towardsfreedom.com>
Subject: [Haskell-beginners] Re: ghci access to .hs functions
To: beginners@haskell.org
Message-ID: <20100812131811.5d904...@gom>
Content-Type: text/plain; charset=US-ASCII

On Thu, 12 Aug 2010 12:00:44 -0300
MAN <elviotoccal...@gmail.com> wrote:

> couple of things
> you could be interested to know.
> 
most definitely! i very much appreciate the help, el.
thx to you too brent for clearing up the ExitCode problem

> Your main will allways be 'IO ()' , but that doesn't mean you must
> sparkle 'return ()' all over the place :P
>
well i have been specializing in random programming => just keep trying
things randomly and hope it works. :D

putting return() in the "all" worked (no idea why), so i thought it
must be a good thing and put it in the other two. :D

i'd also used mapM because map didn't work and i figured it had
something to do with monads and M is the first letter in monad. :D

i really have to get away from this sort of thing and i'm trying to
figure out the excellent stuff etugrul and kyle provided in the 
= vs <- thread.

now i tried taking the returns out and things are fine for "add" and
"upd", but even with the changes you suggested for gtKys (mapM to
mapM_) i'm getting these errors:

======
gadit.hs:30:19:
    Couldn't match expected type `()' against inferred type `[()]'
      Expected type: IO ()
      Inferred type: IO [()]
    In the expression: gtKys conn
    In a case alternative: "all" -> gtKys conn

gadit.hs:66:4:
    Couldn't match expected type `[()]' against inferred type `()'
      Expected type: IO [()]
      Inferred type: IO ()
    In the expression: mapM_ (mkPag conn) kL
    In the expression:
        do { r <- quickQuery conn "SELECT key from main" [];
             let kL = concat $ map (map fromSql) r;
             mapM_ (mkPag conn) kL }
=======

it want some sort of list and i'm not providing it.

here is the code in question with the line numbers:

=======

 21 main = do
 22     args <- getArgs
 23     let act = head args
 24     conn <- connectPostgreSQL "host=localhost dbname=lohv
 user=pradmin"
 25     case act of
 26          "add"  -> do
 27              kV1 <- dbDef conn
 28              upDbs conn (fromSql kV1)
 29          "upd"  -> upDbs conn (last args)
 30          "all"  -> gtKys conn
 31          _      -> putStrLn "add, upd num, all only!!"
 32     commit conn
 33     disconnect conn
 34     putStrLn "All Done!"

...

 61 -- gtKys: gets all key values in database
 62 gtKys :: (IConnection conn) => conn -> IO [()]
 63 gtKys conn = do
 64     r <- quickQuery conn "SELECT key from main" []
 65     let kL = concat $ map (map fromSql) r
 66     mapM_ (mkPag conn) kL

========

now i got to thinking about all this and realized that gtKys really
shouldn't have 
mapM_ (mkPag conn) kL 
in there anyway because its job is to just get some key values not to
make Pages (mkPag)
in fact, i only put it in there because i couldn't figure out how to
get the stuff out - as kyle says in the other thread: 
"once something is "inside" of a monad (IO in this case), it's very
difficult, impossible, to get it out again."

so what i did is rewrite the code like this:
case act of
...
         "all"  -> do
             kyL <- gtKys conn
             mapM_ (mkPag conn) kyL

and 

gtKys conn = do
    r <- quickQuery conn "SELECT key from main" []
    return $ concat $ map (map fromSql) r

it all works now.

gtKys now has the lengthy type:
gtKys :: (IConnection conn, Data.Convertible.Base.Convertible SqlValue
a) => conn -> IO [a]

which i'm leaving out since it generates a scope error unless i import
something else (as brent explained in the above post regarding
ExitCode).

however, i still don't quite understand what the return is doing beyond
you seem to need it in order to get things out of a monad associated
function. whenever i have an IO () i seem to require it.

there seem to be several ways to ask functions to provide computations
and require specific ways to get access to them.


-- 
In friendship,
prad

                                      ... with you on your journey
Towards Freedom
http://www.towardsfreedom.com (website)
Information, Inspiration, Imagination - truly a site for soaring I's


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

Message: 2
Date: Thu, 12 Aug 2010 18:08:47 -0300
From: MAN <elviotoccal...@gmail.com>
Subject: Re: [Haskell-beginners] Re: ghci access to .hs functions
To: prad <p...@towardsfreedom.com>
Cc: beginners@haskell.org
Message-ID: <1281647328.4114.30.ca...@dy-book>
Content-Type: text/plain; charset="UTF-8"

The problem in the "all" case branch is that, although you applied the
mapM-to-mapM_ modification, you didn't change the type signature of
gtKys accordingly:

  mapM  :: (a -> m b) -> m a -> m [b]
  mapM_ :: (a -> m b) -> m a -> m ()

In your case 'a' above is whatever 'fromSql' returns for your program (I
can't infer it... which might explain the lengthy type signature), and
'b' is simply '()'. So 'b=()' which means the type of 'gtKys' is no
longer:

  gtKys :: (IConnection conn) => conn -> IO [()] -- using 'mapM'

  gtKys :: (IConnection conn) => conn -> IO ()   -- using 'mapM_'


Two more things to say:

You should know that '()' is both a type AND a value... kind of strange.
'()' designates a type of "things" (like 'Int' and 'Double' do for
integers and double-precision numbers), but the kink is that the only
"thing" of such type is a value known as 'unit' which is written (for
good or bad) '()'. 

As a mental help... all functions in Control.Monad (and several other
modules as well) that end in '_' "throw away" their results; meaning
that they return 'unit' regardless of their action.

"however, i still don't quite understand what the return is doing beyond
you seem to need it in order to get things out of a monad associated
function." Pan, I think It's time for you to get serious with the monads
XD I can't suggest anything, 'cause I read a whole lot before my brain
started to understand any of it... but maybe you should check out
articles, looking for real monad-related answers to your more general
questions (in particular you seem to be getting hit by "getting a value
out of a monad").
Try the en.wikibooks.org/wiki/Haskell or learnyouahaskell.org and skip
to the sections where do-notation and monadic computations are
discussed. Just rememeber: "Don't Panic".

El jue, 12-08-2010 a las 13:18 -0700, prad escribió:
> On Thu, 12 Aug 2010 12:00:44 -0300
> MAN <elviotoccal...@gmail.com> wrote:
> 
> > couple of things
> > you could be interested to know.
> > 
> most definitely! i very much appreciate the help, el.
> thx to you too brent for clearing up the ExitCode problem
> 
> > Your main will allways be 'IO ()' , but that doesn't mean you must
> > sparkle 'return ()' all over the place :P
> >
> well i have been specializing in random programming => just keep trying
> things randomly and hope it works. :D
> 
> putting return() in the "all" worked (no idea why), so i thought it
> must be a good thing and put it in the other two. :D
> 
> i'd also used mapM because map didn't work and i figured it had
> something to do with monads and M is the first letter in monad. :D
> 
> i really have to get away from this sort of thing and i'm trying to
> figure out the excellent stuff etugrul and kyle provided in the 
> = vs <- thread.
> 
> now i tried taking the returns out and things are fine for "add" and
> "upd", but even with the changes you suggested for gtKys (mapM to
> mapM_) i'm getting these errors:
> 
> ======
> gadit.hs:30:19:
>     Couldn't match expected type `()' against inferred type `[()]'
>       Expected type: IO ()
>       Inferred type: IO [()]
>     In the expression: gtKys conn
>     In a case alternative: "all" -> gtKys conn
> 
> gadit.hs:66:4:
>     Couldn't match expected type `[()]' against inferred type `()'
>       Expected type: IO [()]
>       Inferred type: IO ()
>     In the expression: mapM_ (mkPag conn) kL
>     In the expression:
>         do { r <- quickQuery conn "SELECT key from main" [];
>              let kL = concat $ map (map fromSql) r;
>              mapM_ (mkPag conn) kL }
> =======
> 
> it want some sort of list and i'm not providing it.
> 
> here is the code in question with the line numbers:
> 
> =======
> 
>  21 main = do
>  22     args <- getArgs
>  23     let act = head args
>  24     conn <- connectPostgreSQL "host=localhost dbname=lohv
>  user=pradmin"
>  25     case act of
>  26          "add"  -> do
>  27              kV1 <- dbDef conn
>  28              upDbs conn (fromSql kV1)
>  29          "upd"  -> upDbs conn (last args)
>  30          "all"  -> gtKys conn
>  31          _      -> putStrLn "add, upd num, all only!!"
>  32     commit conn
>  33     disconnect conn
>  34     putStrLn "All Done!"
> 
> ...
> 
>  61 -- gtKys: gets all key values in database
>  62 gtKys :: (IConnection conn) => conn -> IO [()]
>  63 gtKys conn = do
>  64     r <- quickQuery conn "SELECT key from main" []
>  65     let kL = concat $ map (map fromSql) r
>  66     mapM_ (mkPag conn) kL
> 
> ========
> 
> now i got to thinking about all this and realized that gtKys really
> shouldn't have 
> mapM_ (mkPag conn) kL 
> in there anyway because its job is to just get some key values not to
> make Pages (mkPag)
> in fact, i only put it in there because i couldn't figure out how to
> get the stuff out - as kyle says in the other thread: 
> "once something is "inside" of a monad (IO in this case), it's very
> difficult, impossible, to get it out again."
> 
> so what i did is rewrite the code like this:
> case act of
> ...
>          "all"  -> do
>              kyL <- gtKys conn
>              mapM_ (mkPag conn) kyL
> 
> and 
> 
> gtKys conn = do
>     r <- quickQuery conn "SELECT key from main" []
>     return $ concat $ map (map fromSql) r
> 
> it all works now.
> 
> gtKys now has the lengthy type:
> gtKys :: (IConnection conn, Data.Convertible.Base.Convertible SqlValue
> a) => conn -> IO [a]
> 
> which i'm leaving out since it generates a scope error unless i import
> something else (as brent explained in the above post regarding
> ExitCode).
> 
> however, i still don't quite understand what the return is doing beyond
> you seem to need it in order to get things out of a monad associated
> function. whenever i have an IO () i seem to require it.
> 
> there seem to be several ways to ask functions to provide computations
> and require specific ways to get access to them.
> 
> 
> -- 
> In friendship,
> prad
> 
>                                       ... with you on your journey
> Towards Freedom
> http://www.towardsfreedom.com (website)
> Information, Inspiration, Imagination - truly a site for soaring I's
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners




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

Message: 3
Date: Thu, 12 Aug 2010 23:15:43 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: ghci access to .hs functions
To: beginners@haskell.org
Cc: prad <p...@towardsfreedom.com>
Message-ID: <201008122315.43788.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Thursday 12 August 2010 22:18:11, prad wrote:
> On Thu, 12 Aug 2010 12:00:44 -0300
>
> MAN <elviotoccal...@gmail.com> wrote:
> > couple of things
> > you could be interested to know.
>
> most definitely! i very much appreciate the help, el.
> thx to you too brent for clearing up the ExitCode problem
>
> > Your main will allways be 'IO ()' , but that doesn't mean you must
> > sparkle 'return ()' all over the place :P
>
> well i have been specializing in random programming => just keep trying
> things randomly and hope it works. :D

That phase shouldn't last long.
Learning to understand the error messages helps getting over it, because 
then most of the time you know from the error message how to fix your code.

>
> putting return() in the "all" worked (no idea why),

Because that gave all branches the same type.

> so i thought it
> must be a good thing and put it in the other two. :D
>
> i'd also used mapM because map didn't work and i figured it had
> something to do with monads and M is the first letter in monad. :D

Good thinking.

mapM :: Monad m => (a -> m b) -> [a] -> m [b]
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()

With map, you go from (a -> m b) and [a] to [m b].
Then you run the monadic actions in that list one after the other and 
either collect the results (mapM) or discard the results (mapM_).

The functions to do that are

sequence :: Monad m => [m b] -> m [b]

and

sequence_ :: Monad m => [m b] -> m ()

mapM fun list = sequence (map fun list)
mapM_ fun list = sequence_ (map fun list)

>
> i really have to get away from this sort of thing and i'm trying to
> figure out the excellent stuff etugrul and kyle provided in the
> = vs <- thread.
>
> now i tried taking the returns out and things are fine for "add" and
> "upd", but even with the changes you suggested for gtKys (mapM to
> mapM_) i'm getting these errors:
>
> ======
> gadit.hs:30:19:
>     Couldn't match expected type `()' against inferred type `[()]'
>       Expected type: IO ()
>       Inferred type: IO [()]
>     In the expression: gtKys conn
>     In a case alternative: "all" -> gtKys conn
>
> gadit.hs:66:4:
>     Couldn't match expected type `[()]' against inferred type `()'
>       Expected type: IO [()]
>       Inferred type: IO ()
>     In the expression: mapM_ (mkPag conn) kL
>     In the expression:
>         do { r <- quickQuery conn "SELECT key from main" [];
>              let kL = concat $ map (map fromSql) r;
>              mapM_ (mkPag conn) kL }
> =======
>
> it want some sort of list and i'm not providing it.
>
> here is the code in question with the line numbers:
>
> =======
>
>  21 main = do
>  22     args <- getArgs
>  23     let act = head args
>  24     conn <- connectPostgreSQL "host=localhost dbname=lohv
>  user=pradmin"


>  25     case act of
>  26          "add"  -> do
>  27              kV1 <- dbDef conn
>  28              upDbs conn (fromSql kV1)
>  29          "upd"  -> upDbs conn (last args)
>  30          "all"  -> gtKys conn
>  31          _      -> putStrLn "add, upd num, all only!!"

In a case expression, all branches must have the same type.
The branches for "add", "upd" and _ have type IO (), so the branch for 
"all" must also have that type.

But the type signature says

gtKys conn :: IO [()]

So GHC can't match the expected type `IO ()' [expected because the other 
branches say it must have that type] against the inferred type `IO [()]' 
['inferred' from the type signature here].

That's the first error message.

But the last statement in gtKys is `mapM_ (mkPag conn) kL'.

mapM_ :: Monad m => (a -> m b) -> [a] -> m ()

so the actual type of gtKys conn is IO () [ and gtKys has the type 
(IConnection conn) => conn -> IO () ]

Fix (or remove) the type signature, and it should work with the old code.

Now to the second error message.
Here the type signature determines the type GHC `expects', IO [()], and the 
code determines the inferred type, IO ().

>  32     commit conn
>  33     disconnect conn
>  34     putStrLn "All Done!"
>
> ...
>
>  61 -- gtKys: gets all key values in database
>  62 gtKys :: (IConnection conn) => conn -> IO [()]
>  63 gtKys conn = do
>  64     r <- quickQuery conn "SELECT key from main" []
>  65     let kL = concat $ map (map fromSql) r
>  66     mapM_ (mkPag conn) kL
>
> ========
>
> now i got to thinking about all this and realized that gtKys really
> shouldn't have
> mapM_ (mkPag conn) kL
> in there anyway because its job is to just get some key values not to
> make Pages (mkPag)
> in fact, i only put it in there because i couldn't figure out how to
> get the stuff out - as kyle says in the other thread:
> "once something is "inside" of a monad (IO in this case), it's very
> difficult, impossible, to get it out again."

That depends on the monad.

>
> so what i did is rewrite the code like this:
> case act of
> ...
>          "all"  -> do
>              kyL <- gtKys conn
>              mapM_ (mkPag conn) kyL
>
> and
>
> gtKys conn = do
>     r <- quickQuery conn "SELECT key from main" []
>     return $ concat $ map (map fromSql) r
>
> it all works now.
>
> gtKys now has the lengthy type:
> gtKys :: (IConnection conn, Data.Convertible.Base.Convertible SqlValue
> a) => conn -> IO [a]
>
> which i'm leaving out since it generates a scope error unless i import
> something else (as brent explained in the above post regarding
> ExitCode).
>
> however, i still don't quite understand what the return is doing beyond
> you seem to need it in order to get things out of a monad associated
> function. whenever i have an IO () i seem to require it.

A common use of `return ()' is to give a monadic computation the correct 
type, e.g.

main = do
    args <- getArgs
    case args of
        [file, limit] -> do somestuff file (read limit)
                            return ()
        _ -> putStrLn usageMessage

if somestuff :: FilePath -> Double -> IO Int

That was what it did here.

Another common use is do nothing, as in

when :: Monad m => Bool -> m () -> m()
when cond action =
    if cond
        then action
        else return ()

>
> there seem to be several ways to ask functions to provide computations
> and require specific ways to get access to them.



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

Message: 4
Date: Thu, 12 Aug 2010 21:11:03 -0400
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: [Haskell-beginners] Restoring interleaved lists?
To: beginners <beginners@haskell.org>
Message-ID:
        <aanlktikhfh4hqwgjht0ovdbuo9jztsaqqoa5qzzdf...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi all,

I'm parsing a file that represents a type of musical notation (Guitar
Pro file format). In the format there are t tracks, each composed of m
measures. In the file the measures are all stored sequentially, i.e.
from measure 1 to measure t*m, in the following fashion:

- measure 1 of track 1 ;
- measure 1 of track 2 ;
- ...
- measure 1 of track t ;
- measure 2 of track 1 ;
- measure 2 of track 2 ;
- ...
- measure 2 of track t ;
- ...
- measure m of track 1 ;
- measure m of track 2 ;
- ...
- measure m of track t ;

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?


Thanks,

Patrick

-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


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

Message: 5
Date: Thu, 12 Aug 2010 18:20:49 -0700 (PDT)
From: Travis Erdman <traviserd...@yahoo.com>
Subject: [Haskell-beginners] Profiling introduces a space leak where
        there   was none before?
To: beginners@haskell.org
Message-ID: <9952.63559...@web114707.mail.gq1.yahoo.com>
Content-Type: text/plain; charset=us-ascii

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


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

Reply via email to