Skip to content

Commit

Permalink
Add an instance for the new SeedGen type class
Browse files Browse the repository at this point in the history
  • Loading branch information
lehins committed Jan 7, 2025
1 parent 2cce257 commit 998989a
Show file tree
Hide file tree
Showing 3 changed files with 39 additions and 4 deletions.
37 changes: 35 additions & 2 deletions System/Random/MWC.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE BangPatterns, CPP, DeriveDataTypeable, FlexibleContexts,
{-# LANGUAGE BangPatterns, CPP, DataKinds, DeriveDataTypeable, FlexibleContexts,
FlexibleInstances, MultiParamTypeClasses, MagicHash, Rank2Types,
ScopedTypeVariables, TypeFamilies, UnboxedTuples, TypeOperators
#-}
Expand Down Expand Up @@ -164,19 +164,26 @@ import Control.Monad.ST (ST,runST)
import Data.Bits ((.&.), (.|.), shiftL, shiftR, xor)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.IORef (IORef, atomicModifyIORef, newIORef)
import Data.Maybe (fromMaybe)

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.10.1

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.6.5

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.2.2

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.4.4

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.6.6

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.8.4

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-13 / ghc 8.6.5

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-13 / ghc 8.4.4

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.6.6

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.12.1

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.10.1

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.10.7

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.2.8

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.8.4

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.8.4

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.2.8

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.12.1

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.4.8

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.4.8

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.0.2

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 8.6.5

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.0.2

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.12.1

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.6.6

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.10.1

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 8.4.4

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-13 / ghc 8.8.4

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-13 / ghc 9.0.2

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 8.10.7

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-13 / ghc 8.10.7

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.2.8

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.4.8

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 8.8.4

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.0.2

The import of ‘Data.Maybe’ is redundant

Check warning on line 167 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.8.4

The import of ‘Data.Maybe’ is redundant
import Data.Typeable (Typeable)
import Data.Vector.Generic (Vector)
import Data.Word
import Data.Kind
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Generic.Mutable as GM
import qualified Data.Vector.Primitive as P

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.10.1

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.6.5

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.2.2

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.4.4

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.6.6

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.8.4

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-13 / ghc 8.6.5

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-13 / ghc 8.4.4

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.6.6

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.12.1

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.10.1

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.10.7

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.2.8

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.8.4

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.8.4

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.2.8

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.12.1

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-latest / ghc 9.4.8

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.4.8

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.0.2

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 8.6.5

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 8.0.2

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.12.1

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.6.6

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.10.1

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 8.4.4

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-13 / ghc 8.8.4

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-13 / ghc 9.0.2

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 8.10.7

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / macOS-13 / ghc 8.10.7

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.2.8

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.4.8

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 8.8.4

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.0.2

The qualified import of ‘Data.Vector.Primitive’ is redundant

Check warning on line 174 in System/Random/MWC.hs

View workflow job for this annotation

GitHub Actions / windows-latest / ghc 9.8.4

The qualified import of ‘Data.Vector.Primitive’ is redundant
import qualified Data.Vector.Unboxed as I
import qualified Data.Vector.Unboxed.Mutable as M
import System.IO (hPutStrLn, stderr)
import System.IO.Unsafe (unsafePerformIO)
import qualified Control.Exception as E
import System.Random.MWC.SeedSource
import qualified System.Random.Stateful as Random
#if MIN_VERSION_random(1,3,0)
import qualified Data.Primitive.ByteArray as Primitive
import qualified Data.Array.Byte as Data
#endif


-- | NOTE: Consider use of more principled type classes
-- 'Random.Uniform' and 'Random.UniformRange' instead.
Expand Down Expand Up @@ -486,6 +493,32 @@ instance PrimMonad m => Random.ThawedGen Seed m where
#endif
thawGen = restore

#if MIN_VERSION_random(1,3,0)
instance Random.SeedGen Seed where
type SeedSize Seed = 1032 -- == 4 * 258
fromSeed = toSeed . P.Vector 0 258 . compatFromPrimByteArray . Random.unSeed
toSeed seed =
seedFromVector $ (P.convert :: I.Vector Word32 -> P.Vector Word32) $ fromSeed seed
where
seedFromVector v =
case v of
P.Vector 0 258 ba ->
fromMaybe (error "ByteArray had an unexpected length") $ Random.mkSeed $ compatToPrimByteArray ba
_ | P.length v == 258 -> seedFromVector $ P.force v
_ -> error $ "Impossible: Seed had an unexpected length of: " ++ show (P.length v)

compatToPrimByteArray :: Data.ByteArray -> Primitive.ByteArray
compatFromPrimByteArray :: Primitive.ByteArray -> Data.ByteArray
#if MIN_VERSION_primitive(0,8,0)
compatToPrimByteArray = id
compatFromPrimByteArray = id
#else
compatToPrimByteArray (Data.ByteArray ba) = Primitive.ByteArray ba
compatFromPrimByteArray (Primitive.ByteArray ba) = Data.ByteArray ba
#endif
#endif


-- | Convert vector to 'Seed'. It acts similarly to 'initialize' and
-- will accept any vector. If you want to pass seed immediately to
-- restore you better call initialize directly since following law holds:
Expand Down Expand Up @@ -582,7 +615,7 @@ nextIndex i = fromIntegral j

-- The multiplicator : 0x5BCF5AB2
--
-- Eventhough it is a 'Word64', it is important for the correctness of the proof
-- Even though it is a 'Word64', it is important for the correctness of the proof
-- on carry value that it is /not/ greater than maxBound 'Word32'.
aa :: Word64
aa = 1540315826
Expand Down
4 changes: 3 additions & 1 deletion mwc-random.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -71,8 +71,10 @@ library
, primitive >= 0.6.2
, random >= 1.2
, time
, vector >= 0.7
, vector >= 0.10.12
, math-functions >= 0.2.1.0
if impl(ghc < 9.4)
build-depends: data-array-byte

ghc-options: -Wall -funbox-strict-fields -fwarn-tabs

Expand Down
2 changes: 1 addition & 1 deletion tests/props.hs
Original file line number Diff line number Diff line change
Expand Up @@ -245,7 +245,7 @@ logProbBinomial n p k
k' = fromIntegral k
nk' = fromIntegral $ n - k


cumulativeChi2 :: Int -> Double -> Double
cumulativeChi2 (fromIntegral -> ndf) x
| x <= 0 = 0
Expand Down

0 comments on commit 998989a

Please sign in to comment.