- 21 Nov, 2014 1 commit
-
-
Herbert Valerio Riedel authored
Summary: The `Data.OldList` module was originally created in 3daf0023 to provide a way to access the original list-specialised functions from `Data.List`. It was also made an exposed module in order to facilitate adapting the `haskell2010`/`haskell98` packages. However, since the `haskell2010`/`haskell98` packages were dropped, we no longer need to expose `Data.OldList`. Depends on D511 Reviewers: ekmett, austin Reviewed By: ekmett, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D513
-
- 20 Nov, 2014 2 commits
-
-
eir@cis.upenn.edu authored
This includes a submodule update for `array`. There is also an added test in libraries/array/tests/T9220.
-
Herbert Valerio Riedel authored
Alas `{-# LANGUAGE Safe #-}` can't be used since `Data.Coerce` isn't "safe". However, we use `coerce` just as an optimisation (see also 4ba884bd which broke the safe-inferred status of `Data.Functor.Identity`), so this module at least deserves `{-# LANGUAGE Trustworthy #-}`. NOTE: `Data.Functor.Identity` was added to `base` in the context of #9664 Reviewed By: luite Differential Revision: https://phabricator.haskell.org/D507
-
- 19 Nov, 2014 1 commit
-
-
Herbert Valerio Riedel authored
This also overrides all optional `Foldable` methods (which would otherwise be default-implemented in terms of `foldMap`) with supposedly optimally minimal implementations. While at it, this also removes the redundant `{-# LANGUAGE CPP #-}`. Reviewed By: austin, dfeuer Differential Revision: https://phabricator.haskell.org/D467
-
- 18 Nov, 2014 6 commits
-
-
Austin Seipp authored
This broke validate due to name shadowing warnings. This reverts commit 1f6b1ab4.
-
Wieland Hoffmann authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
Austin Seipp authored
Reviewed-by:
Edward Kmett <ekmett@gmail.com> Authored-by: Yalas, Scott Turner Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
David Feuer authored
Summary: Instead, describe what it actually does. Reviewers: austin, ekmett, simonpj, hvr Reviewed By: austin, ekmett Subscribers: simonpj, thomie, carter Projects: #ghc Differential Revision: https://phabricator.haskell.org/D448
-
David Feuer authored
Summary: Make listArray fuse with a list producer. Note: if code size increases too much, we can fix that with some `RULES`. Reviewers: nomeata, hvr, austin, ekmett, simonmar, bgamari Reviewed By: bgamari Subscribers: bgamari, thomie, carter Differential Revision: https://phabricator.haskell.org/D474 GHC Trac Issues: #9801
-
Yuras authored
Summary: It describes a work around Trac #3838, but it is already fixed and the workaround removed, Trac #7653 Test Plan: not needed Reviewers: hvr, Mikolaj, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D478
-
- 13 Nov, 2014 5 commits
-
-
David Feuer authored
Implement an `amap`/`coerce` rule in `GHC.Arr` to match the `map`/`coerce` rule in GHC.Base. In order to do so, delay inlining `amap` until phase 1. To prevent the inlining delay from causing major inefficiencies due to missed list fusion, rewrite `amap` to avoid relying on list fusion. This has the extra benefit of reducing the size of the compiled amap code by skipping the impossible case of an array with a negative size. Reviewed By: nomeata Differential Revision: https://phabricator.haskell.org/D471
-
David Feuer authored
Previously, `Array`s were simply converted to lists, and the list methods used. That works acceptably well for `foldr` and `foldr1`, but not so sensibly for most other things. Left folds ended up "twisted" the way they are for lists, leading to surprising performance characteristics. Moreover, this implements `length` and `null` so they check the array size directly. Finally, a test is added to the testsuite ensuring the overridden `Foldable` methods agree with their expected default semantics. Addresses #9763 Reviewed By: hvr, austin Differential Revision: https://phabricator.haskell.org/D459
-
David Feuer authored
This avoids duplication in `GHC.Base`; originally, we had mapM f = sequence . map f This led to excessive allocation in `cryptarithm2`. Defining sequence = mapM id does not appear to cause any `nofib` problems. Reviewed By: hvr Differential Revision: https://phabricator.haskell.org/D470
-
David Feuer authored
Make `words` a good producer and `unwords` a good consumer for list fusion. Thus `unwords . words` will avoid producing an intermediate list of words, although it will produce each individual word. Make `unwords` slightly lazier, so that `unwords (s : undefined) = s ++ undefined` instead of `= undefined`. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D375
-
David Feuer authored
Make the comment on the map/coerce rule refer to the right section in the paper; give the full name of the papers, and name its authors. [skip ci] Differential Revision: https://phabricator.haskell.org/D472
-
- 12 Nov, 2014 2 commits
-
-
Simon Marlow authored
This reverts commit f0fcc41d. New changes: now works on 32-bit platforms too. I added some basic support for 64-bit subtraction and comparison operations to the x86 NCG.
-
Herbert Valerio Riedel authored
This is done as a separate `integer-gmp2` backend library because it turned out to become a complete rewrite from scratch. Due to the different (over)allocation scheme and potentially different accounting (via the new `{shrink,resize}MutableByteArray#` primitives), some of the nofib benchmarks actually results in increased allocation numbers (but not necessarily an increase in runtime!). I believe the allocation numbers could improve if `{resize,shrink}MutableByteArray#` could be optimised to reallocate in-place more efficiently. Here are the more apparent changes in the latest nofib comparision between `integer-gmp` and `integer-gmp2`: ------------------------------------------------------------------ Program Size Allocs Runtime Elapsed TotalMem ------------------------------------------------------------------ ... bernouilli +1.6% +15.3% 0.132 0.132 0.0% ... cryptarithm1 -2.2% 0.0% -9.7% -9.7% 0.0% ... fasta -0.7% -0.0% +10.9% +10.9% 0.0% ... kahan +0.6% +38.9% 0.169 0.169 0.0% ... lcss -0.7% -0.0% -6.4% -6.4% 0.0% ... mandel +1.6% +33.6% 0.049 0.049 0.0% ... pidigits +0.8% +8.5% +3.9% +3.9% 0.0% power +1.4% -23.8% -18.6% -18.6% -16.7% ... primetest +1.3% +50.1% 0.085 0.085 0.0% ... rsa +1.6% +53.4% 0.026 0.026 0.0% ... scs +1.2% +6.6% +6.5% +6.6% +14.3% ... symalg +1.0% +9.5% 0.010 0.010 0.0% ... transform -0.6% -0.0% -5.9% -5.9% 0.0% ... ------------------------------------------------------------------ Min -2.3% -23.8% -18.6% -18.6% -16.7% Max +1.6% +53.4% +10.9% +10.9% +14.3% Geometric Mean -0.3% +1.9% -0.8% -0.8% +0.0% (see P35 / https://phabricator.haskell.org/P35 for full report) By default, `INTEGER_LIBRARY=integer-gmp2` is active now, which results in the package `integer-gmp-1.0.0.0` being registered in the package db. The previous `integer-gmp-0.5.1.0` can be restored by setting `INTEGER_LIBRARY=integer-gmp` (but will probably be removed altogether for GHC 7.12). In-tree GMP support has been stolen from the old `integer-gmp` (while unpatching the custom memory-allocators, as well as forcing `-fPIC`) A minor hack to `ghc-cabal` was necessary in order to support two different `integer-gmp` packages (in different folders) with the same package key. There will be a couple of follow-up commits re-implementing some features that were dropped to keep D82 minimal, as well as further clean-ups/improvements. More information can be found via #9281 and https://ghc.haskell.org/trac/ghc/wiki/Design/IntegerGmp2 Reviewed By: austin, rwbarton, simonmar Differential Revision: https://phabricator.haskell.org/D82
-
- 11 Nov, 2014 2 commits
-
-
David Feuer authored
Use fewer left/right-biased folds for defaults and functions in `Data.Foldable`, to better support things that don't look like cons lists. This also extends the Haddock docstrings in `Data.Foldable`. Reviewed By: hvr, ekmett Differential Revision: https://phabricator.haskell.org/D441
-
David Feuer authored
Define list monad operations using list comprehensions. Code using monad operations with lists did not fuse fully. Writing list code with `do` notation or `(>>=)` and `(>>)` operations could allocate more than equivalent code using list comprehensions. Define `mapM` directly, instead of using `sequence` and `map`. This leads to substantially less allocation in `cryptarithm2`. Addresses #9781 Reviewed By: ekmett, nomeata Differential Revision: https://phabricator.haskell.org/D455
-
- 10 Nov, 2014 1 commit
-
-
Herbert Valerio Riedel authored
This also updates the `transformers` submodule to the just released `transformers-0.4.2.0` package version. See #9664 for more details Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D313
-
- 08 Nov, 2014 2 commits
-
-
David Feuer authored
Control.Applicative previously imported `(.)` and `id` from `Control.Arrow`, but then only applied them to functions. Reviewed By: ekmett, hvr Differential Revision: https://phabricator.haskell.org/D462
-
Herbert Valerio Riedel authored
This is a follow-up commit to df3b1d43
-
- 07 Nov, 2014 5 commits
-
-
thomie authored
This makes nub and nubBy behave as specified in the Haskell 98 Report. This reverts 0ad9def5, and fixes #3280, #7913 and #2528 (properly). Before this change, the output of `T2528` was (4x wrong): ``` [A,B] [1,2] False False ``` Reviewed By: dfeuer, ekmett, austin, hvr Differential Revision: https://phabricator.haskell.org/D238
-
Herbert Valerio Riedel authored
This commit mostly converts literate comments into ordinary Haskell comments or sometimes even Haddock comments, while also removing literate comments in a few cases where they don't make much sense anymore. Moreover, in a few cases trailing whitespaces were removed as well. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D456
-
Merijn Verstraaten authored
Summary: My previous attempt to fix the new coercion bug introduced by my fix actually just reverted back to the *old* bug. This time it should properly handle all three size scenarios. Signed-off-by:
Merijn Verstraaten <merijn@inconsistent.nl> Test Plan: validate Reviewers: dfeuer, austin, hvr Reviewed By: austin, hvr Subscribers: thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D407 GHC Trac Issues: #8089
-
David Feuer authored
It's prettier that way, and there's less risk of anything going sideways. Reviewed By: hvr, simonpj Differential Revision: https://phabricator.haskell.org/D450
-
David Feuer authored
Generally clean up things relating to Applicative and Monad in `GHC.Base` and `Control.Applicative` to make `Applicative` feel like a bit more of a first-class citizen rather than just playing second fiddle to `Monad`. Use `coerce` and GND to improve performance and clarity. Change the default definition of `(*>)` to use `(<$)`, in case the `Functor` instance optimizes that. Moreover, some manually written instances are made into compiler-derived instances. Finally, this also adds a few AMP-related laws to the `Applicative` docstring. NOTE: These changes result in a 13% decrease in allocation for T9020 Reviewed By: ekmett, hvr Differential Revision: https://phabricator.haskell.org/D432
-
- 06 Nov, 2014 1 commit
-
-
mjo authored
Add doctest examples for every data type and function in `Data.Either` Differential Revision: https://phabricator.haskell.org/D443
-
- 05 Nov, 2014 3 commits
-
-
bernalex authored
Niklas Hambüchen suggested that we add the dual of `subsequences`, isSubsequenceOf (like `isPrefixOf` to `inits` & `isSuffixOf` to `tails`). It was a simple and noncontroversial proposal which passed unanimously. For more details see the original proposal discussion at https://www.haskell.org/pipermail/libraries/2014-November/024063.html Differential Revision: https://phabricator.haskell.org/D435Signed-off-by:
Alexander Berntsen <alexander@plaimi.net>
-
Herbert Valerio Riedel authored
This mostly cleans up irregularities introduced in 68255588 (re D352) as well as making sure Haddock is able to resolve all references.
-
David Feuer authored
New `Foldable` methods accidentally had `Foldable` contexts, which led to type roles being assigned incorrectly and preventing GND from deriving `Foldable` instances. Removing those fixes #9761. Moreover, this patch takes advantage of this fix by deriving `Foldable` (and `Eq`) for `UniqFM`. Differential Revision: https://phabricator.haskell.org/D425
-
- 04 Nov, 2014 6 commits
-
-
Herbert Valerio Riedel authored
Those manual descriptions in Haddock strings have become redundant since Haddock gained the ability to print the minimal complete definition as specified via `{-# MINIMAL #-}` annotation (or otherwise inferred by GHC). Moreover, this commit moves all `{-# MINIMAL #-}` annotations in `base` to the start of the respective `class` definitions, as this is more readable and matches more closely the way Haddock renders that information.
-
Herbert Valerio Riedel authored
This was broken in d94de872 when `join` was inserted between `Monad`'s Haddock string and the `class Monad m` definition thereby breaking the association.
-
Herbert Valerio Riedel authored
This removes the redundant "Minimal complete definition"-block included in the Haddock comment since Haddock renders the `MINIMAL`-pragma as well (which has is moved to the start of `class` definition for better readability of the source code) Morever, the references to `testBitDefault`, `bitDefault`, and `popCountDefault` have been moved to the respective methods' Haddock strings for which they can be used.
-
Herbert Valerio Riedel authored
[skip ci]
-
David Feuer authored
Complete #9759. Use `coerce` to get nicer definitions of `Sum` and `Product`; update documentation for `First` and `Last`. Reviewed By: hvr Differential Revision: https://phabricator.haskell.org/D422
-
David Feuer authored
Fixes #9742. Previously, `foldr1` as applied to a list-like structure would be strict in the spine, and `foldl1` would be strict in the spine of a snoc-list. See also https://www.haskell.org/pipermail/libraries/2014-October/024035.html Differential Revision: https://phabricator.haskell.org/D423
-
- 02 Nov, 2014 2 commits
-
-
Joachim Breitner authored
This increases the chance of good code after fusing a left fold. See ticket #7994 and the new Note [Left folds via right fold] Differential Revision: https://phabricator.haskell.org/D393
-
Joachim Breitner authored
to allow the programer to explictitly set the oneShot flag. This helps with #7994 and will be used in left folds. Also see https://ghc.haskell.org/trac/ghc/wiki/OneShot This commit touches libraries/base/GHC/Event/Manager.hs (which used to have a local definition of the name oneShot) to avoid a shadowing error. Differential Revision: https://phabricator.haskell.org/D392
-
- 31 Oct, 2014 1 commit
-
-
mjo authored
hvr made some suggestions in D352 and D371, this fixes them in the already-applied patch for Data/Bool.hs as well for consistency. Reviewed By: austin, hvr Differential Revision: https://phabricator.haskell.org/D379
-