Skip to content

Commit

Permalink
add Levy alpha-stable
Browse files Browse the repository at this point in the history
  • Loading branch information
Patrick Perry committed Jan 13, 2009
1 parent 328ea7b commit 03b3712
Show file tree
Hide file tree
Showing 3 changed files with 29 additions and 1 deletion.
2 changes: 2 additions & 0 deletions NEWS
@@ -1,6 +1,8 @@

Changes in 0.3:

* Add Levy alpha-Stable distributions.

* Add Summary.Bool for indicators.

* Move Summary to Data.Summary
Expand Down
18 changes: 18 additions & 0 deletions lib/Control/Monad/MC/Base.hs
Expand Up @@ -38,6 +38,16 @@ class (Monad m, HasRNG m) => MonadMC m where
-- | @normal mu sigma@ generates a Normal random variable with mean
-- @mu@ and standard deviation @sigma@.
normal :: Double -> Double -> m Double

-- | @levy c alpha@ gets a Levy alpha-stable variate with scale @c@ and
-- exponent @alpha@. The algorithm only works for @0 < alpha <= 2@.
levy :: Double -> Double -> m Double

-- | @levySkew c alpha beta @ gets a skew Levy alpha-stable variate
-- with scale @c@, exponent @alpha@, and skewness @beta@. The skew
-- parameter must lie in the range @[-1,1]@. The algorithm only works
-- for @0 < alpha <= 2@.
levySkew :: Double -> Double -> Double -> m Double

-- | @poisson mu@ generates a Poisson random variable with mean @mu@.
poisson :: Double -> m Int
Expand All @@ -63,6 +73,10 @@ instance MonadMC GSL.MC where
{-# INLINE uniformInt #-}
normal = GSL.normal
{-# INLINE normal #-}
levy = GSL.levy
{-# INLINE levy #-}
levySkew = GSL.levySkew
{-# INLINE levySkew #-}
poisson = GSL.poisson
{-# INLINE poisson #-}
unsafeInterleaveMC = GSL.unsafeInterleaveMC
Expand All @@ -82,6 +96,10 @@ instance (Monad m) => MonadMC (GSL.MCT m) where
{-# INLINE uniformInt #-}
normal mu sigma = GSL.liftMCT $ GSL.normal mu sigma
{-# INLINE normal #-}
levy c alpha = GSL.liftMCT $ GSL.levy c alpha
{-# INLINE levy #-}
levySkew c alpha beta = GSL.liftMCT $ GSL.levySkew c alpha beta
{-# INLINE levySkew #-}
poisson mu = GSL.liftMCT $ GSL.poisson mu
{-# INLINE poisson #-}
unsafeInterleaveMC = GSL.unsafeInterleaveMCT
Expand Down
10 changes: 9 additions & 1 deletion lib/Control/Monad/MC/GSLBase.hs
Expand Up @@ -41,6 +41,8 @@ module Control.Monad.MC.GSLBase (
uniform,
uniformInt,
normal,
levy,
levySkew,
poisson,
) where

Expand Down Expand Up @@ -257,7 +259,7 @@ setRNG (RNG r') = MC $ \r -> GSL.copyRNG r r'

-- | Get a Mersenne Twister random number generator seeded with the given
-- value.
mt19937 :: Word64 -> RNG
mt19937 :: Seed -> RNG
mt19937 s = unsafePerformIO $ do
r <- GSL.newRNG GSL.mt19937
GSL.setSeed r s
Expand Down Expand Up @@ -289,3 +291,9 @@ normal mu sigma = MC $ \r -> liftM (mu +) (getGaussianRatioMethod r sigma)

poisson :: Double -> MC Int
poisson mu = MC $ \r -> getPoisson r mu

levy :: Double -> Double -> MC Double
levy c alpha = MC $ \r -> getLevy r c alpha

levySkew :: Double -> Double -> Double -> MC Double
levySkew c alpha beta = MC $ \r -> getLevySkew r c alpha beta

0 comments on commit 03b3712

Please sign in to comment.