Bugfix for parallel package

Daniel Fischer daniel.is.fischer at googlemail.com
Mon May 16 16:45:36 CEST 2011


Hi,

since libraries@ is the maintainer of parallel, I send the patch for
http://hackage.haskell.org/trac/ghc/ticket/5100 here.

nonempty-chunks fixes the bug, whitespace removes trailing whitespace in 
Control.Parallel.Strategies, version-bump bumps the version to 3.1.0.2.

Please review.
-------------- next part --------------
1 patch for repository http://darcs.haskell.org/packages/parallel:

Mon May 16 16:23:46 CEST 2011  Daniel Fischer <daniel.is.fischer at googlemail.com>
  * Ensure non-empty chunks (#5100)

  parListChunks produced a stack-overflow if the chunk-size parameter was
  less than 1, as reported in  http://hackage.haskell.org/trac/ghc/ticket/5100.
  This patch makes sure that no non-empty chunks are produced.

New patches:

[Ensure non-empty chunks (#5100)
Daniel Fischer <daniel.is.fischer at googlemail.com>**20110516142346
 Ignore-this: 20b1530ed1a369a4cea382ad46762143
 
 parListChunks produced a stack-overflow if the chunk-size parameter was
 less than 1, as reported in  http://hackage.haskell.org/trac/ghc/ticket/5100
 This patch makes sure that no non-empty chunks are produced.
] hunk ./Control/Parallel/Strategies.hs 426
 --
 parListChunk :: Int -> Strategy a -> Strategy [a]
 parListChunk n strat xs =
-  concat `fmap` parList (evalList strat) (chunk n xs)
+  concat `fmap` parList (evalList strat) (chunk (max 1 n) xs)
+        -- Ensure that chunk doesn't produce an infinite list of empty lists,
+        -- which it would do for n < 1, causing a stack-overflow,
+        -- cf. #5100
 
 chunk :: Int -> [a] -> [[a]]
 chunk _ [] = []

Context:

[TAG git migration
Ian Lynagh <igloo at earth.li>**20110331135045
 Ignore-this: 31dd9f6ef055455751f877956ed9e847
] 
Patch bundle hash:
18c7c3bcbab463142aebd2e3f2499ed57668193d
-------------- next part --------------
Removed trailing whitespace
1 patch for repository http://darcs.haskell.org/packages/parallel:

Mon May 16 16:21:36 CEST 2011  Daniel Fischer <daniel.is.fischer at googlemail.com>
  * Trailing whitespace

New patches:

[Trailing whitespace
Daniel Fischer <daniel.is.fischer at googlemail.com>**20110516142136
 Ignore-this: 89aeafc0ace7ca214740d8d6e7e32176
] {
hunk ./Control/Parallel/Strategies.hs 6
 -- Module      :  Control.Parallel.Strategies
 -- Copyright   :  (c) The University of Glasgow 2001-2010
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  libraries at haskell.org
 -- Stability   :  experimental
 -- Portability :  portable
hunk ./Control/Parallel/Strategies.hs 31
 --
 --  * 'Monad' and 'Applicative' instances are provided, for quickly building
 --    strategies that involve traversing structures in a regular way.
--- 
+--
 -- For API history and changes in this release, see "Control.Parallel.Strategies#history".
 
 -----------------------------------------------------------------------------
hunk ./Control/Parallel/Strategies.hs 122
     -- $history
 
     -- * Backwards compatibility
-    
+
     -- | These functions and types are all deprecated, and will be
     -- removed in a future release.  In all cases they have been
     -- either renamed or replaced with equivalent functionality.
hunk ./Control/Parallel/Strategies.hs 150
 -- Eval monad (isomorphic to Lift monad from MonadLib 3.6.1)
 
 -- | 'Eval' is a Monad that makes it easier to define parallel
--- strategies.  It is a strict identity monad: that is, in 
+-- strategies.  It is a strict identity monad: that is, in
 --
 --  > m >>= f
 --
hunk ./Control/Parallel/Strategies.hs 229
 -- | A 'Strategy' is a function that embodies a parallel evaluation strategy.
 -- The function traverses (parts of) its argument, evaluating subexpressions
 -- in parallel or in sequence.
--- 
+--
 -- A 'Strategy' may do an arbitrary amount of evaluation of its
 -- argument, but should not return a value different from the one it
 -- was passed.
hunk ./Control/Parallel/Strategies.hs 240
 -- intention is that the program applies the 'Strategy' to a
 -- structure, and then uses the returned value, discarding the old
 -- value.  This idiom is expressed by the 'using' function.
--- 
+--
 type Strategy a = a -> Eval a
 
 -- | Evaluate a value using the given 'Strategy'.
hunk ./Control/Parallel/Strategies.hs 252
 
 -- | evaluate a value using the given 'Strategy'.  This is simply
 -- 'using' with the arguments reversed.
--- 
+--
 withStrategy :: Strategy a -> a -> a
 withStrategy = flip using
 
hunk ./Control/Parallel/Strategies.hs 256
--- | Compose two strategies sequentially. 
+-- | Compose two strategies sequentially.
 -- This is the analogue to function composition on strategies.
 --
 -- > strat2 `dot` strat1 == strat2 . withStrategy strat1
hunk ./Control/Parallel/Strategies.hs 352
 -- --------------------------------------------------------------------------
 -- Strategy combinators for Traversable data types
 
--- | Evaluate the elements of a traversable data structure 
+-- | Evaluate the elements of a traversable data structure
 -- according to the given strategy.
 evalTraversable :: Traversable t => Strategy a -> Strategy (t a)
 evalTraversable = traverse
hunk ./Control/Parallel/Strategies.hs 446
 -- The non-compositional 'parListWHNF' might be more efficient than its
 -- more compositional counterpart; use RULES to do the specialisation.
 
-{-# RULES 
+{-# RULES
  "parList/rseq" parList rseq = parListWHNF
  #-}
 
hunk ./Control/Parallel/Strategies.hs 458
 -- > parMap strat f = withStrategy strat . map f
 --
 parMap :: Strategy b -> (a -> b) -> [a] -> [b]
-parMap strat f = (`using` parList strat) . map f 
+parMap strat f = (`using` parList strat) . map f
 
 -- --------------------------------------------------------------------------
 -- Strategies for lazy lists
hunk ./Control/Parallel/Strategies.hs 482
 -- 'evalBuffer' is not as compositional as the type suggests. In fact,
 -- it evaluates list elements at least to weak head normal form,
 -- disregarding a strategy argument 'r0'.
--- 
+--
 -- > evalBuffer n r0 == evalBuffer n rseq
 --
 evalBuffer :: Int -> Strategy a -> Strategy [a]
hunk ./Control/Parallel/Strategies.hs 513
 -- Deforest the intermediate list in parBuffer/evalBuffer when it is
 -- unnecessary:
 
-{-# RULES 
+{-# RULES
 "evalBuffer/rseq"  forall n . evalBuffer  n rseq = evalBufferWHNF n
 "parBuffer/rseq"   forall n . parBuffer   n rseq = parBufferWHNF  n
  #-}
hunk ./Control/Parallel/Strategies.hs 606
 f $|| s = \ x -> let z = x `using` s in z `par` f z
 
 -- | Sequential function composition. The result of
--- the second function is evaluated using the given strategy, 
+-- the second function is evaluated using the given strategy,
 -- and then given to the first function.
 (.|) :: (b -> c) -> Strategy b -> (a -> b) -> (a -> c)
hunk ./Control/Parallel/Strategies.hs 609
-(.|) f s g = \ x -> let z = g x `using` s in 
+(.|) f s g = \ x -> let z = g x `using` s in
                     z `pseq` f z
 
 -- | Parallel function composition. The result of the second
hunk ./Control/Parallel/Strategies.hs 616
 -- function is evaluated using the given strategy,
 -- in parallel with the application of the first function.
 (.||) :: (b -> c) -> Strategy b -> (a -> b) -> (a -> c)
-(.||) f s g = \ x -> let z = g x `using` s in 
+(.||) f s g = \ x -> let z = g x `using` s in
                     z `par` f z
 
hunk ./Control/Parallel/Strategies.hs 619
--- | Sequential inverse function composition, 
+-- | Sequential inverse function composition,
 -- for those who read their programs from left to right.
hunk ./Control/Parallel/Strategies.hs 621
--- The result of the first function is evaluated using the 
+-- The result of the first function is evaluated using the
 -- given strategy, and then given to the second function.
 (-|) :: (a -> b) -> Strategy b -> (b -> c) -> (a -> c)
hunk ./Control/Parallel/Strategies.hs 624
-(-|) f s g = \ x -> let z = f x `using` s in 
+(-|) f s g = \ x -> let z = f x `using` s in
                     z `pseq` g z
 
 -- | Parallel inverse function composition,
hunk ./Control/Parallel/Strategies.hs 629
 -- for those who read their programs from left to right.
--- The result of the first function is evaluated using the 
--- given strategy, in parallel with the application of the 
+-- The result of the first function is evaluated using the
+-- given strategy, in parallel with the application of the
 -- second function.
 (-||) :: (a -> b) -> Strategy b -> (b -> c) -> (a -> c)
hunk ./Control/Parallel/Strategies.hs 633
-(-||) f s g = \ x -> let z = f x `using` s in 
+(-||) f s g = \ x -> let z = f x `using` s in
                     z `par` g z
 
 -- -----------------------------------------------------------------------------
hunk ./Control/Parallel/Strategies.hs 655
 
 {-# DEPRECATED (>|) "Use pseq or $| instead" #-}
 -- | DEPRECATED: Use 'pseq' or '$|' instead
-(>|) :: Done -> Done -> Done 
+(>|) :: Done -> Done -> Done
 (>|) = Prelude.seq
 
 {-# DEPRECATED (>||) "Use par or $|| instead" #-}
hunk ./Control/Parallel/Strategies.hs 660
 -- | DEPRECATED: Use 'par' or '$||' instead
-(>||) :: Done -> Done -> Done 
+(>||) :: Done -> Done -> Done
 (>||) = par
 
 {-# DEPRECATED rwhnf "renamed to rseq" #-}
hunk ./Control/Parallel/Strategies.hs 721
 
   The original Strategies design is described in /Algorithm + Strategy = Parallelism/ <http://www.macs.hw.ac.uk/~dsg/gph/papers/html/Strategies/strategies.html>
   and the code was written by
-     Phil Trinder, Hans-Wolfgang Loidl, Kevin Hammond et al. 
+     Phil Trinder, Hans-Wolfgang Loidl, Kevin Hammond et al.
 
 Version 2.x
 
hunk ./Control/Parallel/Strategies.hs 785
 (version 2.3 was not released on Hackage).
 
 Version 3 introduced a major overhaul of the API, to match what is
-presented in the paper 
+presented in the paper
 
   /Seq no More: Better Strategies for Parallel Haskell/
   <http://www.haskell.org/~simonmar/papers/strategies.pdf>
hunk ./Control/Parallel/Strategies.hs 797
 
  * Changes to the naming scheme: 'rwhnf' renamed to 'rseq',
    'seqList' renamed to 'evalList', 'seqPair' renamed to
-   'evalTuple2', 
+   'evalTuple2',
 
 The naming scheme is now as follows:
 
hunk ./Control/Parallel/Strategies.hs 804
   * Basic polymorphic strategies (of type @'Strategy' a@) are called @r... at .
     Examples: 'r0', 'rseq', 'rpar', 'rdeepseq'.
 
-  * A strategy combinator for a particular type constructor 
+  * A strategy combinator for a particular type constructor
     or constructor class @T@ is called @evalT...@, @parT...@ or @seqT... at .
 
   * The @seqT...@ combinators (residing in module
}

Context:

[TAG git migration
Ian Lynagh <igloo at earth.li>**20110331135045
 Ignore-this: 31dd9f6ef055455751f877956ed9e847
] 
Patch bundle hash:
e8f977e9579970c8c40b9d88f89e1275831cbdd2
-------------- next part --------------
1 patch for repository http://darcs.haskell.org/packages/parallel:

Mon May 16 16:29:53 CEST 2011  Daniel Fischer <daniel.is.fischer at googlemail.com>
  * Bump version

  Minor version bump because of fix to http://hackage.haskell.org/trac/ghc/ticket/5100.

New patches:

[Bump version
Daniel Fischer <daniel.is.fischer at googlemail.com>**20110516142953
 Ignore-this: d5824bc9df1ebc1090efe262fb9f1fb5
 
 Minor version bump because of fix to #5100.
] hunk ./parallel.cabal 2
 name:		parallel
-version:	3.1.0.1
+version:	3.1.0.2
 license:	BSD3
 license-file:	LICENSE
 maintainer:	libraries at haskell.org

Context:

[TAG git migration
Ian Lynagh <igloo at earth.li>**20110331135045
 Ignore-this: 31dd9f6ef055455751f877956ed9e847
] 
Patch bundle hash:
ee4aec87bae97f463c57c5435c5f440cc0fafbe3


More information about the Libraries mailing list