Hello All
I am trying to understand the Strategies ( http://hackage.haskell.org/packages/archive/parallel/3.2.0.2/doc/html/Control-Parallel-Strategies.html ) and wrote this quick code.

import Data.List
import Control.Parallel.Strategies



fun :: [ Int ] -> [ Int ]
fun [] = []
fun ( x : xs ) = ( x + 1 ) : fun xs


main = do
   let xs =  ( fun [ 1..1000000 ] ) `using` parListChunk 500000 rdeepseq
   return ()


When I am running this code  due to laziness , the xs is not evaluating.

[mukesh.tiwari@user ParallelStrat]$ time ./Main  +RTS -N1 -s
          48,320 bytes allocated in the heap
           5,928 bytes copied during GC
          38,592 bytes maximum residency (1 sample(s))
          14,656 bytes maximum slop
               1 MB total memory in use (0 MB lost due to fragmentation)

                                    Tot time (elapsed)  Avg pause  Max pause
  Gen  0         0 colls,     0 par    0.00s    0.00s     0.0000s    0.0000s
  Gen  1         1 colls,     0 par    0.00s    0.00s     0.0002s    0.0002s

  Parallel GC work balance: -nan (0 / 0, ideal 1)

                        MUT time (elapsed)       GC time  (elapsed)
  Task  0 (worker) :    0.00s    (  0.00s)       0.00s    (  0.00s)
  Task  1 (worker) :    0.00s    (  0.00s)       0.00s    (  0.00s)
  Task  2 (bound)  :    0.00s    (  0.00s)       0.00s    (  0.00s)

  SPARKS: 0 (0 converted, 0 overflowed, 0 dud, 0 GC'd, 0 fizzled)

  INIT    time    0.00s  (  0.00s elapsed)
  MUT     time    0.00s  (  0.00s elapsed)
  GC      time    0.00s  (  0.00s elapsed)
  EXIT    time    0.00s  (  0.00s elapsed)
  Total   time    0.00s  (  0.00s elapsed)

  Alloc rate    48,368,368 bytes per MUT second

  Productivity   0.0% of total user, 0.0% of total elapsed

gc_alloc_block_sync: 0
whitehole_spin: 0
gen[0].sync: 0
gen[1].sync: 0

real	0m0.003s
user	0m0.002s
sys	0m0.001s


[mukesh.tiwari@user ParallelStrat]$ time ./Main  +RTS -N2 -s
          48,248 bytes allocated in the heap
              40 bytes copied during GC
          38,440 bytes maximum residency (1 sample(s))
          18,904 bytes maximum slop
               2 MB total memory in use (0 MB lost due to fragmentation)

                                    Tot time (elapsed)  Avg pause  Max pause
  Gen  0         0 colls,     0 par    0.00s    0.00s     0.0000s    0.0000s
  Gen  1         1 colls,     0 par    0.00s    0.00s     0.0001s    0.0001s

  Parallel GC work balance: -nan (0 / 0, ideal 2)

                        MUT time (elapsed)       GC time  (elapsed)
  Task  0 (worker) :    0.00s    (  0.00s)       0.00s    (  0.00s)
  Task  1 (bound)  :    0.00s    (  0.00s)       0.00s    (  0.00s)
  Task  2 (worker) :    0.00s    (  0.00s)       0.00s    (  0.00s)

  SPARKS: 0 (0 converted, 0 overflowed, 0 dud, 0 GC'd, 0 fizzled)

  INIT    time    0.00s  (  0.00s elapsed)
  MUT     time    0.00s  (  0.00s elapsed)
  GC      time    0.00s  (  0.00s elapsed)
  EXIT    time    0.00s  (  0.00s elapsed)
  Total   time    0.00s  (  0.00s elapsed)

  Alloc rate    48,248,000,000,000 bytes per MUT second

  Productivity 100.0% of total user, 0.0% of total elapsed

gc_alloc_block_sync: 0
whitehole_spin: 0
gen[0].sync: 0
gen[1].sync: 0

real	0m0.004s
user	0m0.000s
sys	0m0.004s

The library doc suggest that parListChunk divides a list into chunks, and applies the strategy evalList strat  to each chunk in parallel. Looking at the source code ( http://hackage.haskell.org/packages/archive/parallel/3.2.0.2/doc/html/src/Control-Parallel-Strategies.html#parListChunk ) , list is  split into chunks and then strategy is applied parallel to every chunk. Could some one please tell me what is wrong with this concept and why the code above is showing laziness.

Regards
Mukesh Tiwari