- 02 Dec, 2014 1 commit
-
-
puffnfresh authored
The QuickCheck property now succeeds: prop :: Fixed B7 -> Bool prop a = read (show a) == a This changes the Show instance for Fixed to round up, rather than down when calculating a digit. This needs to happen because Read also rounds down: data B7 instance HasResolution B7 where resolution _ = 128 1 / 128 = 0.0078125 read "0.007" = (0.000 :: Fixed B7) Here is an example of the change to Show: showFixed False (0.009 :: Fixed B7) -- Broken: "0.007" -- Fixed: "0.008" And now Read can continue to round down: read "0.008" = (0.0078125 :: Fixed B7) Reviewed By: hvr, ekmett Differential Revision: https://phabricator.haskell.org/D547
-
- 25 Nov, 2014 1 commit
-
-
Herbert Valerio Riedel authored
[skip ci]
-
- 24 Nov, 2014 2 commits
-
-
Herbert Valerio Riedel authored
See b0534f78 for more details [skip ci]
-
Ömer Sinan Ağacan authored
Summary: Implementation of #5364. Mostly boilerplate, reading FILE fields is missing. Test Plan: - Get some feedback on missing parts. (FILE fields) - Get some feedback on module name. - Get some feedback on other things. - Get code reviewed. - Make sure test suite is passing. (I haven't run it myself) Reviewers: hvr, austin, ezyang Reviewed By: ezyang Subscribers: ekmett, simonmar, ezyang, carter, thomie Differential Revision: https://phabricator.haskell.org/D306 GHC Trac Issues: #5364 Conflicts: includes/rts/Flags.h
-
- 23 Nov, 2014 1 commit
-
-
Carter Schonwald authored
The actual type-signatures of the new instances are: instance Storable a => Storable (Complex a) instance (Storable a, Integral a) => Storable (Ratio a) See also https://groups.google.com/d/msg/haskell-core-libraries/mjBSo2CQ3LU/0gwg0QvviOIJ Addresses #9826 Reviewed By: ekmett Differential Revision: https://phabricator.haskell.org/D519
-
- 22 Nov, 2014 1 commit
-
-
Herbert Valerio Riedel authored
This implements a `Natural` type for representing unsigned arbitrary precision integers. When available, `integer-gmp>=1.0.0`'s `BigNat` type is used as building-block to construct `Natural` as an algebraic data-type. Otherwise, `Natural` falls back being a `newtype`-wrapper around `Integer` (as is done in Edward Kmett's `nats` package). The `GHC.Natural` module exposes an internal GHC-specific API, while `Numeric.Natural` provides the official & portable API. Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D473
-
- 21 Nov, 2014 6 commits
-
-
spl authored
The new function `Data.Bits.toIntegralSized` provides a similar functionality to `fromIntegral` but adds validation that the argument fits in the result type's size. The implementation of `toIntegralSized` has been derived from `intCastMaybe` (which is part of Herbert Valerio Riedel's `int-cast` package, see http://hackage.haskell.org/package/int-cast) Addresses #9816 Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D512
-
snoyberg authored
Defaults to using `show` to prevent any breakage of existing code. Also provide a custom implementation for `SomeException` which uses the underlying exception's `displayException`. Differential Revision: https://phabricator.haskell.org/D517
-
Alex Petrov authored
fillBytes uses 'memset' to fill a memory area with a given byte value. Reviewed By: austin, hvr Differential Revision: https://phabricator.haskell.org/D465
-
Herbert Valerio Riedel authored
This adds the module `Data.Void` (formerly provided by Edward Kmett's `void` package) to `base`. The original Haskell98 compatible implementation has been modified to use modern GHC features (among others this makes use of `EmptyCase` as motivated by #2431), and `vacuousM` was dropped since it's redundant now with the AMP in place. Instances for classes not part of `base` had to be dropped as well. TODO: Documentation could be improved Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D506
-
David Feuer authored
Summary: Fixes #9368 Reviewers: nomeata, hvr, ekmett, austin Reviewed By: ekmett, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D498 GHC Trac Issues: #9368
-
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
-
- 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
-
- 07 Nov, 2014 1 commit
-
-
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
-
- 05 Nov, 2014 1 commit
-
-
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>
-
- 04 Nov, 2014 1 commit
-
-
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
-
- 31 Oct, 2014 1 commit
-
-
Herbert Valerio Riedel authored
The internal Unicode definitions were updated via d4fd1680 [skip ci]
-
- 26 Oct, 2014 1 commit
-
-
Herbert Valerio Riedel authored
This adds the module `Data.Bifunctor` providing the `Bifunctor(bimap,first,second)` class and a couple of instances This module and the class were previously exported by the `bifunctors` package. In contrast to the original module all `INLINE` pragmas have been removed. Reviewed By: ekmett, austin, dolio Differential Revision: https://phabricator.haskell.org/D336
-
- 18 Oct, 2014 2 commits
-
-
Herbert Valerio Riedel authored
With this change `Control.Monad.foldM` becomes an alias for `Data.Foldable.foldlM`. Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D251
-
mgmeier authored
This finally removes the `Data.OldTypeable` module (which has been deprecated in 7.8), from `base`, compiler and testsuite. The deprecated `Typeable{1..7}` aliases in `Data.Typeable` are not removed yet in order to give existing code a bit more time to adapt. Reviewed By: hvr, dreixel Differential Revision: https://phabricator.haskell.org/D311
-
- 01 Oct, 2014 4 commits
-
-
David Feuer authored
analogously to mapM. Fixes #9546.
-
David Feuer authored
This fixes #9502.
-
David Feuer authored
This fixes #9355.
-
David Feuer authored
in order to make its RULES semantics preserving. This fixes #9495.
-
- 28 Sep, 2014 1 commit
-
-
Herbert Valerio Riedel authored
Generalise `when`/`unless`from `Monad` to `Applicative` and `guard` from `MonadPlus` to `Alternative` respectively. This was made possible by the AMP and is somewhat related to #9586 (but generalising in the context of the AMP instead of the FTP) Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D253
-
- 21 Sep, 2014 2 commits
-
-
Herbert Valerio Riedel authored
This finally exposes also the methods of these 3 classes in the Prelude in order to allow to define basic class instances w/o needing imports. This almost completes the primary goal of #9586 NOTE: `fold`, `foldl'`, `foldr'`, and `toList` are not exposed yet, as they require upstream fixes for at least `containers` and `bytestring`, and are not required for defining basic instances. Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D236
-
Herbert Valerio Riedel authored
This flips the switch and replaces the entities in `Data.List`/`Control.Monad` conflicting with `Data.{Foldable,Traversable}` with re-exports of the more general versions. As of this commit, the code below (which is also added as a test-case) compiles w/o error. module XPrelude (module X) where import Control.Monad as X import Data.Foldable as X import Data.List as X import Data.Monoid as X import Data.Traversable as X import Prelude as X This addresses #9568 Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D235
-
- 20 Sep, 2014 3 commits
-
-
Herbert Valerio Riedel authored
-
Herbert Valerio Riedel authored
This replaces the entities in Data.List conflicting with Data.Foldable with re-exports of the generalised version from Data.Foldable. As of this commit, the following compiles w/o error module XPrelude (module X) where import Control.Monad as X import Data.Foldable as X import Data.List as X import Prelude as X Reviewed By: austin, dfeuer, ekmett Differential Revision: https://phabricator.haskell.org/D229
-
Herbert Valerio Riedel authored
Turn `toList`, `elem`, `sum`, `product`, `maximum`, and `minimum` into `Foldable` methods. This helps avoiding regressions (and semantic differences) while implementing #9586 Reviewed By: austin, dfeuer, ekmett Differential Revision: https://phabricator.haskell.org/D231
-
- 19 Sep, 2014 1 commit
-
-
Herbert Valerio Riedel authored
This was probably just an oversight. With this change the fixity matches that from `Data.List.{elem,notElem`}`. Addresses #9610 Reviewed By: austin, ekmett Differential Revision: https://phabricator.haskell.org/D227
-
- 09 Sep, 2014 1 commit
-
-
Herbert Valerio Riedel authored
Since we now had to major bump due to AMP being landed, `base-4.7.1.0` is not gonna happen, as we're going straight for a `base-4.8.0.0` release. [skip ci] since this is a doc-only change
-
- 04 Sep, 2014 1 commit
-
-
Herbert Valerio Riedel authored
This is a follow-up commit to e428b5b8 (refs D195 & #9550)
-
- 31 Aug, 2014 2 commits
-
-
Herbert Valerio Riedel authored
This exposes the newly added CLZ/CTZ primops from e0c1767d (re #9340) via two new methods `countLeadingZeros` and `countTrailingZeros` in the `Data.Bits.FiniteBits` class. The original proposal can be found at http://www.haskell.org/pipermail/libraries/2014-August/023567.html Test Plan: successful validate Reviewers: ekmett, tibbe GHC Trac Issues: #9532 Differential Revision: https://phabricator.haskell.org/D158
-
Herbert Valerio Riedel authored
The original proposal text can be found at http://www.haskell.org/pipermail/libraries/2014-August/023491.html The proposal passed with a clear majority, and was additionally confirmed by the core libraries committee. *Compatibility Note* Only code that imports `Data.Word` for the sole purpose of using `Word` *and* requires to be `-Werror`-clean (due to `-fwarn-unused-imports`) is affected by this change. In order to write warning-free forward/backward compatible against `base`, a variant of the following CPP-based snippet can be used: -- Starting with base>4.7.0 or GHC>7.8 Prelude re-exports 'Word' -- The following is needed, if 'Word' is the *only* entity needed from Data.Word #ifdef MIN_VERSION_base # if !MIN_VERSION_base(4,7,1) import Data.Word (Word) # endif -- no cabal_macros.h -- fallback to __GLASGOW_HASKELL__ #elif __GLASGOW_HASKELL__ < 709 import Data.Word (Word) #endif This also updates the haddock submodule in order to avoid a compile warning
-
- 19 Aug, 2014 2 commits
-
-
bernalex authored
Summary: Make the `Float` and `Double` implementations of `signum` handle -0.0 correctly per IEEE-754. This, together with "Make Prelude.abs handle -0.0 correctly (#7858)", fixes Trac #7858. Depends on D145 Signed-off-by:
Alexander Berntsen <alexander@plaimi.net> Test Plan: signum of (-0.0) should be (-0.0) not 0.0. Test program: main = putStrLn $ p ++ " " ++ n where f = show . signum p = f (-0.0 :: Double) n = f (0.0 :: Double) Reviewers: ekmett, hvr, rwbarton, austin Reviewed By: austin Subscribers: phaskell, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D148 GHC Trac Issues: #7858
-
bernalex authored
Summary: Make the `Float` and `Double` implementations of `abs` handle -0.0 correctly per IEEE-754. abs (-0.0::Float) and abs (-0.0::Double) previously returned -0.0, when they should return 0.0. This patch fixes this. Signed-off-by:
Alexander Berntsen <alexander@plaimi.net> Test Plan: abs (-0.0::Double) should = 0.0 instead of (-0.0) Reviewers: ekmett, hvr, austin, rwbarton Reviewed By: austin, rwbarton Subscribers: phaskell, trofi, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D145 GHC Trac Issues: #7858
-
- 20 Jul, 2014 1 commit
-
-
bernalex authored
Summary: Carl Howells pointed out[0] that the `Monoid` instance for `Data.Proxy.Proxy` is only defined for types with kind *. This is a very mild change. Furthermore, Edward Kmett revealed[1] that it was supposed to be there all along -- the extension simply got lost in commit 1d1ff77a, as pointed out by Adam Vogt[2]. This used to be correct in GHC 7.6, so this commit fixes a regression. This addresses #9317. [0] <http://www.haskell.org/pipermail/libraries/2014-July/023261.html>. [1] <http://www.haskell.org/pipermail/libraries/2014-July/023267.html>. [2] <http://www.haskell.org/pipermail/libraries/2014-July/023265.html>. Signed-off-by:
Alexander Berntsen <alexander@plaimi.net> Test Plan: See [0] Reviewers: austin, hvr, ekmett Reviewed By: austin, hvr, ekmett Subscribers: phaskell, simonmar, relrod, carter Differential Revision: https://phabricator.haskell.org/D70
-
- 11 Jul, 2014 1 commit
-
-
Herbert Valerio Riedel authored
-
- 14 May, 2014 1 commit
-
-
bernalex authored
A strict (<$>) has been proposed numerous times. The first time around[1] by Johan Tibell, and the last time around[2] by David Luposchainsky. David's thread was able to avoid The Bikeshed Monster, and his (<$!>) proposal received unanimous +1s all around. This addresses #9099. [1]: http://www.haskell.org/pipermail/libraries/2013-November/021728.html [2]: http://www.haskell.org/pipermail/libraries/2014-April/022864.htmlAuthored-by:
Alexander Berntsen <alexander@plaimi.net> Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-