-
Notifications
You must be signed in to change notification settings - Fork 0
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Add missing int64/word64-to-double/float rules (#23907)
CLC proposal: haskell/core-libraries-committee#203 (cherry picked from commit 5126a2f)
- Loading branch information
Showing
4 changed files
with
144 additions
and
0 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,67 @@ | ||
module T23907 (loop) where | ||
|
||
import Data.Word | ||
import Data.Bits | ||
|
||
{-# NOINLINE loop #-} | ||
loop :: Int -> Double -> SMGen -> (Double, SMGen) | ||
loop 0 !a !s = (a, s) | ||
loop n !a !s = loop (n - 1) (a + b) t where (b, t) = nextDouble s | ||
|
||
mix64 :: Word64 -> Word64 | ||
mix64 z0 = | ||
-- MurmurHash3Mixer | ||
let z1 = shiftXorMultiply 33 0xff51afd7ed558ccd z0 | ||
z2 = shiftXorMultiply 33 0xc4ceb9fe1a85ec53 z1 | ||
z3 = shiftXor 33 z2 | ||
in z3 | ||
|
||
shiftXor :: Int -> Word64 -> Word64 | ||
shiftXor n w = w `xor` (w `shiftR` n) | ||
|
||
shiftXorMultiply :: Int -> Word64 -> Word64 -> Word64 | ||
shiftXorMultiply n k w = shiftXor n w * k | ||
|
||
nextWord64 :: SMGen -> (Word64, SMGen) | ||
nextWord64 (SMGen seed gamma) = (mix64 seed', SMGen seed' gamma) | ||
where | ||
seed' = seed + gamma | ||
|
||
nextDouble :: SMGen -> (Double, SMGen) | ||
nextDouble g = case nextWord64 g of | ||
(w64, g') -> (fromIntegral (w64 `shiftR` 11) * doubleUlp, g') | ||
|
||
data SMGen = SMGen !Word64 !Word64 -- seed and gamma; gamma is odd | ||
|
||
mkSMGen :: Word64 -> SMGen | ||
mkSMGen s = SMGen (mix64 s) (mixGamma (s + goldenGamma)) | ||
|
||
goldenGamma :: Word64 | ||
goldenGamma = 0x9e3779b97f4a7c15 | ||
|
||
floatUlp :: Float | ||
floatUlp = 1.0 / fromIntegral (1 `shiftL` 24 :: Word32) | ||
|
||
doubleUlp :: Double | ||
doubleUlp = 1.0 / fromIntegral (1 `shiftL` 53 :: Word64) | ||
|
||
mix64variant13 :: Word64 -> Word64 | ||
mix64variant13 z0 = | ||
-- Better Bit Mixing - Improving on MurmurHash3's 64-bit Finalizer | ||
-- http://zimbry.blogspot.fi/2011/09/better-bit-mixing-improving-on.html | ||
-- | ||
-- Stafford's Mix13 | ||
let z1 = shiftXorMultiply 30 0xbf58476d1ce4e5b9 z0 -- MurmurHash3 mix constants | ||
z2 = shiftXorMultiply 27 0x94d049bb133111eb z1 | ||
z3 = shiftXor 31 z2 | ||
in z3 | ||
|
||
mixGamma :: Word64 -> Word64 | ||
mixGamma z0 = | ||
let z1 = mix64variant13 z0 .|. 1 -- force to be odd | ||
n = popCount (z1 `xor` (z1 `shiftR` 1)) | ||
-- see: http://www.pcg-random.org/posts/bugs-in-splitmix.html | ||
-- let's trust the text of the paper, not the code. | ||
in if n >= 24 | ||
then z1 | ||
else z1 `xor` 0xaaaaaaaaaaaaaaaa |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,57 @@ | ||
|
||
==================== Tidy Core ==================== | ||
Result size of Tidy Core | ||
= {terms: 90, types: 62, coercions: 0, joins: 0/3} | ||
|
||
$WSMGen | ||
= \ conrep conrep1 -> | ||
case conrep of { W64# unbx -> | ||
case conrep1 of { W64# unbx1 -> SMGen unbx unbx1 } | ||
} | ||
|
||
Rec { | ||
$wloop | ||
= \ ww ww1 ww2 ww3 -> | ||
case ww of ds { | ||
__DEFAULT -> | ||
let { seed' = plusWord64# ww2 ww3 } in | ||
let { | ||
x# | ||
= timesWord64# | ||
(xor64# seed' (uncheckedShiftRL64# seed' 33#)) | ||
18397679294719823053#Word64 } in | ||
let { | ||
x#1 | ||
= timesWord64# | ||
(xor64# x# (uncheckedShiftRL64# x# 33#)) | ||
14181476777654086739#Word64 } in | ||
$wloop | ||
(-# ds 1#) | ||
(+## | ||
ww1 | ||
(*## | ||
(word2Double# | ||
(word64ToWord# | ||
(uncheckedShiftRL64# | ||
(xor64# x#1 (uncheckedShiftRL64# x#1 33#)) 11#))) | ||
1.1102230246251565e-16##)) | ||
seed' | ||
ww3; | ||
0# -> (# ww1, ww2, ww3 #) | ||
} | ||
end Rec } | ||
|
||
loop | ||
= \ ds a s -> | ||
case ds of { I# ww -> | ||
case a of { D# ww1 -> | ||
case s of { SMGen ww2 ww3 -> | ||
case $wloop ww ww1 ww2 ww3 of { (# ww4, ww5, ww6 #) -> | ||
(D# ww4, SMGen ww5 ww6) | ||
} | ||
} | ||
} | ||
} | ||
|
||
|
||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters