- Feb 26, 2014
-
-
Austin Seipp authored
We had started relying on GMP 5.x (for usage of mpz_powm_sec), but this is pretty painful on RHEL-esque targets, which still use GMP 4.x. In the mean time while we're still supporting this, it's easier to just fallback to mpz_powm when _sec is unavailable, and emit a WARNING for using the primitive. This also installs a header, HsIntegerGmp.h, which clients could use for a fallback. As a side note, this will probably also help Debian oldstable users who might have outdated GMP versions (which I believe is the cause for #8666.) Reviewed-by:
Herbert Valerio Riedel <hvr@gnu.org> Signed-off-by:
Austin Seipp <austin@well-typed.com> (cherry picked from commit d7bff4dd)
-
- Feb 02, 2014
-
-
Herbert Valerio Riedel authored
High-level pseudo code of what the code was supposed to implement: quotRem' :: Integer -> Integer -> (Integer,Integer) quotRem' a b@(S# _) | b < 0 = negFst . uncurry quotRem' . negSnd $ (a,b) | otherwise = quotRemUI a (fromIntegral (abs b)) divMod' :: Integer -> Integer -> (Integer,Integer) divMod' a b@(S# _) | b < 0 = negSnd . uncurry divMod' . negBoth $ (a,b) | otherwise = divModUI a (fromIntegral b) negFst (q,r) = (-q,r) negSnd (q,r) = ( q,-r) negBoth (q,r) = (-q,-r) -- quotRemUI and divModUI represent GMP's `mpz_{f,t}div_qr_ui()` quotRemUI, divModUI :: Integer -> Word -> (Integer,Integer) Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Feb 01, 2014
-
-
Gabor Greif authored
Herbert, this is a merge candidate to the 7.8 branch
-
Herbert Valerio Riedel authored
Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Jan 31, 2014
-
-
Herbert Valerio Riedel authored
Among other things, this unhides `GHC.Integer` and re-groups the export list. Moreover, the internal representation of `Integer` is explained a bit more, and `/Since: 0.5.1.0/` annotations have been added. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Jan 16, 2014
-
-
Herbert Valerio Riedel authored
This is due to `mpz_*()` functions having @long@ arguments which are 32bit on IL32P64, whereas `Int#` and `Word#` are 64bit wide, causing all sorts of malfunction due to truncation. This affects mostly the new big/small-int primops introduced in the course of #8647, so when `SIZEOF_W != SIZEOF_LONG` we simply fall back to using the big/big-int primops. big/small primops implemented via the low-level `mpn_*()` GMP operations are not affected, as those use `mp_limb_t` arguments. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
This allows to simplify code in `float.c` and to encode the "sizeof(mp_limb_t) != sizeof(W_)" assumption as a compile-time assertion. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Jan 14, 2014
-
-
Herbert Valerio Riedel authored
I'm a bit surprised though this didn't cause linkage errors (the incorrect import statement was introduced in 7bdcadda) Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
kazu-yamamoto authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
- Jan 13, 2014
-
-
Herbert Valerio Riedel authored
This is similiar to what has been done in [af2ba9c8/integer-gmp] for `gmpz_tdiv_{q,r,qr}_ui` (re #8647); However, the gain is more modest here, as performance-conscious code tends to use `quot`/`rem` rather than `div`/`mod`: Program Size Allocs Runtime Elapsed TotalMem ------------------------------------------------------------- primetest +0.3% -2.4% 0.06 0.06 +0.0% rsa +0.2% -3.3% 0.02 0.02 +0.0% Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
We now allocate a 1-limb mpz_t on the stack instead of doing a more expensive heap-allocation (especially if the heap-allocated copy becomes garbage right away); this addresses #8647. In order to delay heap allocations of 1-limb `ByteArray#`s instead of the previous `(# Int#, ByteArray# #)` pair, a 3-tuple `(# Int#, ByteArray#, Word# #)` is returned now. This tuple is given the type-synonym `MPZ#`. This 3-tuple representation uses either the 1st and the 2nd element, or the 1st and the 3rd element to represent the limb(s) (NB: undefined `ByteArray#` elements must not be accessed as they don't point to a proper `ByteArray#`, see also `DUMMY_BYTE_ARR`); more specifically, the following encoding is used (where `⊥` means undefined/unused): - (# 0#, ⊥, 0## #) -> value = 0 - (# 1#, ⊥, w #) -> value = w - (# -1#, ⊥, w #) -> value = -w - (# s#, d, 0## #) -> value = J# s d The `mpzToInteger` helper takes care of converting `MPZ#` into an `Integer`, and allocating a 1-limb `ByteArray#` in case the value (`w`/`-w`) doesn't fit the `S# Int#` representation). The following nofib benchmarks benefit from this optimization: Program Size Allocs Runtime Elapsed TotalMem ------------------------------------------------------------------ bernouilli +0.2% -5.2% 0.12 0.12 +0.0% gamteb +0.2% -1.7% 0.03 0.03 +0.0% kahan +0.3% -13.2% 0.17 0.17 +0.0% mandel +0.2% -24.6% 0.04 0.04 +0.0% power +0.2% -2.6% -2.0% -2.0% -8.3% primetest +0.1% -17.3% 0.06 0.06 +0.0% rsa +0.2% -18.5% 0.02 0.02 +0.0% scs +0.1% -2.9% -0.1% -0.1% +0.0% sphere +0.3% -0.8% 0.03 0.03 +0.0% symalg +0.2% -3.1% 0.01 0.01 +0.0% ------------------------------------------------------------------ Min +0.1% -24.6% -4.6% -4.6% -8.3% Max +0.3% +0.0% +5.9% +5.9% +4.5% Geometric Mean +0.2% -1.0% +0.2% +0.2% -0.0% Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Jan 10, 2014
-
-
Herbert Valerio Riedel authored
This fixes the actual cause for #8661, i.e. a mismatch between the actual arity of the Cmm implementation and the arity declared in the foreign import statement. This also reverts [a3878d17/integer-gmp] as the workaround isn't needed anymore. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
Forgot to add this chunk to the commit [a3878d17/integer-gmp] Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
I still need to investigated, but for some reason not yet obvious to me, commit [af2ba9c8/integer-gmp] (re #8647) seems to have triggered #8661 on linux/32 This commit disables the use of the `quotRemIntegerWord#` primop on 32bit (which seems to trigger the issue). Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Jan 08, 2014
-
-
Herbert Valerio Riedel authored
This avoids allocating this special value over and over again every time it's needed, and therefore this addresses #8647. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
This is useful as `quot`/`rem` are often used with small-int divisors, like when computing the digits of an `Integer`. This optimization reduces allocations in the following `nofib` benchmarks: Program Size Allocs Runtime Elapsed TotalMem ----------------------------------------------------------------- power +0.3% -0.8% -1.2% -1.2% +0.0% primetest +0.3% -3.9% 0.07 0.07 +0.0% rsa +0.3% -4.0% 0.02 0.02 +0.0% symalg +0.2% -1.4% 0.01 0.01 +0.0% This addresses #8647 Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Jan 07, 2014
-
-
Austin Seipp authored
See the comments and #8102. The basic gist of it seems to be that the build system follows an implied rule from somewhere to directly build a C file, which doesn't have a dependency on the in-tree gmp.h that we build. As a result, the C file compilation races against the GMP build, causing an error. This is a pretty unsatisfactory hack, but for Windows and OS X machines where we more often build in-tree GMPs, it's quite important. Authored-by:
Kazu Yamamoto <kazu@iij.ad.jp> Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
- Jan 04, 2014
-
-
Herbert Valerio Riedel authored
This adds `{plus,minus}IntegerInt#` which help to reduce temporary allocations in `plusInteger` and `minusInteger`. This and the previous commit introducing `timesIntegerInt#` (i.e. baeeef7a) result in reduced allocations for the following nofib benchmarks on Linux/amd64: Program Size Allocs Runtime Elapsed TotalMem ------------------------------------------------------------------ bernouilli +0.0% -4.2% 0.12 0.12 +0.0% kahan +0.1% -12.6% 0.17 0.17 +0.0% pidigits +0.0% -0.5% -4.7% -4.5% +0.0% power +0.0% -2.7% +3.1% +3.1% +9.1% primetest +0.0% -4.2% 0.07 0.07 +0.0% rsa +0.0% -4.1% 0.02 0.02 +0.0% scs +0.0% -2.6% -0.8% -0.7% +0.0% ------------------------------------------------------------------ Min +0.0% -12.6% -4.7% -4.5% -5.0% Max +0.1% +0.2% +3.1% +3.1% +9.1% Geometric Mean +0.1% -0.3% -0.0% +0.0% +0.1% ------------------------------------------------------------------ Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
This primop helps reducing allocation by being able to pass one `S#` argument directly to the GMP multiplication primitive without needing to promote (and thus allocate a `ByteArray#` as well) the `J#` first. This benefits a few nofib benchmarks wrt to allocations (having most impact on `kahan` resulting in about 10% less allocations) Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
This factors out the recurring task of converting mpz_t structures to/from Int#/ByteArrays# pairs and makes the code more readable. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Jan 03, 2014
-
-
Herbert Valerio Riedel authored
GCC is able to generate better code when using `memcpy` instead of manually copying bytes in a loop. Otoh, `stgAllocForGMP` is typically called for enlarging initial single-limb structures (see also #8647 for more information) and so this minor optimization won't be very visible in measurements. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
Otoh, `divModInt#` is not a proper primop (it's implemented as wrapper around `quotRemInt#` in `GHC.Base`), so we can't do the same for `divModInteger` yet. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Simon Peyton Jones authored
-
- Jan 02, 2014
-
-
Herbert Valerio Riedel authored
Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Nov 24, 2013
-
-
Herbert Valerio Riedel authored
This should improve the check for a suitable installed GMP version, to implicitly check if GMP provides __gmpz_powm_sec() which has been added in GMP version 5.0.0 and switch to the in-tree GMP 5.0.3 source otherwise. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Nov 07, 2013
-
-
Herbert Valerio Riedel authored
Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
These are supposed to be called with `J#`-kind `Integer`s, so check that constructor first. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
These follow closely the existing implementations for `importIntegerFromByteArray` and `exportIntegerToMutableByteArray`. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
This renames to more verbose names which include the type these operations import/export from/to: - `importIntegerFromByteArray`, and - `exportIntegerToMutableByteArray`. This follows the naming convention used for other primitive operations, such as the recently added `copyMutableByteArrayToAddr` operation. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Nov 05, 2013
-
-
Herbert Valerio Riedel authored
This is a follow-up to e94799c9 fixing the Cmm implementation of the primops based on suggestions by Duncan Coutts. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
This adds the following new (internal) primitives {{{#!hs sizeInBaseInteger :: Integer -> Int# -> Word# exportInteger :: Integer -> MutableByteArray# s -> Word# -> Int# -> State# s -> (# State# s, Word# #) importInteger :: ByteArray# -> Word# -> Word# -> Int# -> Integer }}} The import/export primitives support selecting most/least significant byte first order as well as using an offset into the byte-arrays. See Haddock comments for more details. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Oct 28, 2013
-
-
Herbert Valerio Riedel authored
This exposes `mpz_probab_prime_p()` and `mpz_nextprime()` as `testPrimeInteger` and `nextPrimeInteger` respectively and is especially useful for cryptographic algorithms such as RSA. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Oct 27, 2013
-
-
Herbert Valerio Riedel authored
This is a follow-up to 97c101b7 which introduced the "ordinary" `powModInteger` operation. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Oct 24, 2013
-
-
Herbert Valerio Riedel authored
Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
This sets a sensible cabal category (i.e. `Numerical`), extends `extra-tmp-{files,files}` to make this package self-contained, updates the bug-report URL, and cleans up the `{-# LANGUAGE #-}` pragma usage in the source code. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
These files are taken from GNU automake 1.13.3 Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Sep 29, 2013
-
-
Herbert Valerio Riedel authored
The extended GCD computation is useful to have for implementing algorithms such as the chinese reminder theorem. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Herbert Valerio Riedel authored
This exposes the GMP functions `mpz_pow_ui()`, `mpz_powm()`, and `mpz_invert()` as `powInteger`, `powModInteger`, and `recipModInteger` respectively in the module `GHC.Integer.GMP.Internals`. Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
- Sep 16, 2013
-
-
Jan Stolarek authored
-
- Sep 11, 2013
-
-
Herbert Valerio Riedel authored
-