Skip to content

Commit

Permalink
Fixture test SSM model for SMC, RMSMC, PMMH and SMC2
Browse files Browse the repository at this point in the history
  • Loading branch information
Manuel Bärenz committed Feb 8, 2023
1 parent 00f46c1 commit 67b7808
Show file tree
Hide file tree
Showing 7 changed files with 75 additions and 0 deletions.
2 changes: 2 additions & 0 deletions monad-bayes.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -162,6 +162,7 @@ test-suite monad-bayes-test
HMM
LDA
LogReg
NonlinearSSM
Sprinkler
TestAdvanced
TestBenchmarks
Expand All @@ -173,6 +174,7 @@ test-suite monad-bayes-test
TestPopulation
TestSampler
TestSequential
TestSSMFixtures
TestStormerVerlet
TestWeighted

Expand Down
2 changes: 2 additions & 0 deletions test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ import TestPipes qualified
import TestPopulation qualified
import TestSampler qualified
import TestSequential qualified
import TestSSMFixtures qualified
import TestStormerVerlet qualified
import TestWeighted qualified

Expand Down Expand Up @@ -167,3 +168,4 @@ main = hspec do
passed7 `shouldBe` True

TestBenchmarks.test
TestSSMFixtures.test
67 changes: 67 additions & 0 deletions test/TestSSMFixtures.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,67 @@
module TestSSMFixtures where

import NonlinearSSM
import Control.Monad.Bayes.Inference.MCMC
import Control.Monad.Bayes.Inference.PMMH as PMMH (pmmh)
import Control.Monad.Bayes.Inference.RMSMC (rmsmcDynamic)
import Control.Monad.Bayes.Inference.SMC
import Control.Monad.Bayes.Inference.SMC2 as SMC2 (smc2)
import Control.Monad.Bayes.Population
import Control.Monad.Bayes.Sampler.Strict (sampleIOfixed)
import Control.Monad.Bayes.Weighted (unweighted)
import Control.Monad.IO.Class (MonadIO (liftIO))
import Test.Hspec
import System.IO (readFile')
import System.IO.Error (catchIOError, isDoesNotExistError)
import Control.Monad (forM_)
import Control.Monad.Bayes.Class (MonadDistribution)

data Alg = SMC | RMSMC | PMMH | SMC2
deriving (Show, Read, Eq, Ord, Enum, Bounded)

algs :: [Alg]
algs = [minBound .. maxBound]

fixtureToFilename :: Alg -> FilePath
fixtureToFilename alg = "test/fixtures/SSM-" ++ show alg ++ ".txt"

type SSMData = [Double]

t = 5

-- FIXME refactor such that it can be reused in ssm benchmark
runAlgFixed :: MonadDistribution m => SSMData -> Alg -> m String

runAlgFixed ys SMC = fmap show $ population $ smc SMCConfig {numSteps = t, numParticles = 10, resampler = resampleMultinomial} (param >>= model ys)

runAlgFixed ys RMSMC = fmap show $ population $
rmsmcDynamic
MCMCConfig {numMCMCSteps = 10, numBurnIn = 0, proposal = SingleSiteMH}
SMCConfig {numSteps = t, numParticles = 10, resampler = resampleSystematic}
(param >>= model ys)

runAlgFixed ys PMMH = fmap show $ unweighted $
pmmh
MCMCConfig {numMCMCSteps = 2, numBurnIn = 0, proposal = SingleSiteMH}
SMCConfig {numSteps = t, numParticles = 3, resampler = resampleSystematic}
param
(model ys)

runAlgFixed ys SMC2 = fmap show $ population $ smc2 t 3 2 1 param (model ys)

testFixture :: Alg -> SpecWith ()
testFixture alg = do
let filename = fixtureToFilename alg
it ("should agree with the fixture " ++ filename) $ do
ys <- sampleIOfixed $ generateData t
fixture <- catchIOError (readFile' filename) $ \e ->
if isDoesNotExistError e
then return ""
else ioError e
sampled <- sampleIOfixed $ runAlgFixed (map fst ys) alg
-- Reset in case of fixture update or creation
writeFile filename sampled
fixture `shouldBe` sampled

test :: SpecWith ()
test = describe "TestSSMFixtures" $ mapM_ testFixture algs
1 change: 1 addition & 0 deletions test/fixtures/SSM-PMMH.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
[[([74405.69500410178,143777.3515026691,195290.64675632896,483878.28639985673,600603.4104497777],1.0),([74405.69500410178,143777.3515026691,195290.64675632896,483878.28639985673,600603.4104497777],1.0),([74405.69500410178,143777.3515026691,195290.64675632896,483878.28639985673,600603.4104497777],1.0)],[([157620.04097610444,26661.523636563594,321204.4219216401,421274.0528523404,487363.3134055787],1.0),([157620.04097610444,26661.523636563594,321204.4219216401,421274.0528523404,487363.3134055787],1.0),([157620.04097610444,26661.523636563594,321204.4219216401,421274.0528523404,487363.3134055787],1.0)],[([-1.2600621067470811e67,-1.3171618074660135e67,3.55155213532486e66,-9.486041679240111e66,-1.4476178361450074e67],1.0),([-1.2600621067470811e67,-1.3171618074660135e67,3.55155213532486e66,-9.486041679240111e66,-1.4476178361450074e67],1.0),([-1.2600621067470811e67,-1.3171618074660135e67,3.55155213532486e66,-9.486041679240111e66,-1.4476178361450074e67],1.0)]]
1 change: 1 addition & 0 deletions test/fixtures/SSM-RMSMC.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
[([61234.923743603955,79039.83817954235,354024.81636628765,225755.73057039993,-78843.37322818518],0.0),([61234.923743603955,-205024.66324964678,-438520.7645656072,-526045.6062936985,17959.08713788638],0.0),([61234.923743603955,130707.33129683959,260276.7204227042,538891.1815485102,432537.1717560617],0.0),([61234.923743603955,425968.16738967673,72802.89417099475,97062.29318414515,-90904.59187690681],0.0),([61234.923743603955,-80888.00179367141,122235.67304475381,48742.27626015559,-149682.32933231423],0.0),([61234.923743603955,43.833902800088254,-417728.0201965655,49565.634594935604,-303943.3354524304],0.0),([61234.923743603955,350501.69936972257,118986.06426751378,99950.78931739656,-60488.53431816819],0.0),([61234.923743603955,-117376.5868812376,116017.94360094423,378976.39475725644,74865.6296219704],0.0),([61234.923743603955,156368.9791422615,-586653.2615030725,-238480.82081038723,51581.15175237715],0.0),([61234.923743603955,-150776.59937461224,-30862.03908288705,200382.13919586508,-107135.36343350058],0.0)]
1 change: 1 addition & 0 deletions test/fixtures/SSM-SMC.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
[([-1.6946443595984358e8,-2.0398900541476977e8,5.988104418627801e8,5.186441087015647e7,-1.1107580460544899e9],3.747925572660412e-147),([-1.6946443595984358e8,1.762322765772586e8,1.3143034131110222e9,2.917359439754021e7,-4.678360689283452e8],3.747925572660412e-147),([-1.6946443595984358e8,-4.978125179866476e8,-6.568379081060445e8,-1.0039010467494124e9,-4.5194462919398534e8],3.747925572660412e-147),([-1.6946443595984358e8,-2.0398900541476977e8,6.65407483202134e8,-1.3610874802534976e9,1.7804869696064534e9],3.747925572660412e-147),([-1.6946443595984358e8,-4.978125179866476e8,-6.568379081060445e8,-1.0039010467494124e9,-4.5194462919398534e8],3.747925572660412e-147),([-1.6946443595984358e8,-7.848111477226721e8,-1.536250656089418e9,-1.2593852525318892e9,9.33478070563457e8],3.747925572660412e-147),([-1.6946443595984358e8,1.762322765772586e8,1.3143034131110222e9,2.917359439754021e7,-4.678360689283452e8],3.747925572660412e-147),([-1.6946443595984358e8,-4.978125179866476e8,-6.568379081060445e8,7.201669253635451e8,-6.528627637915363e8],3.747925572660412e-147),([-1.6946443595984358e8,-4.978125179866476e8,-6.568379081060445e8,7.201669253635451e8,-6.528627637915363e8],3.747925572660412e-147),([-1.6946443595984358e8,-7.848111477226721e8,-1.536250656089418e9,-1.2593852525318892e9,9.33478070563457e8],3.747925572660412e-147)]
1 change: 1 addition & 0 deletions test/fixtures/SSM-SMC2.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
[([([-9090.483553160731,-18364.240866577857,38447.317849110055,-3829.950678281628,-18689.938602553048],0.3333333333333341),([-9090.483553160731,-18364.240866577857,38447.317849110055,-3829.950678281628,-18689.938602553048],0.3333333333333341),([-9090.483553160731,-18364.240866577857,38447.317849110055,25131.836867847727,47603.03068211828],0.3333333333333341)],9.474658864966518e-180),([([-2.2418721864335723e9,2.4219211687208967e9,5.4463793547824545e9,7.074651672385337e8,2.595090695345872e8],0.3333333333333341),([-2.2418721864335723e9,2.4219211687208967e9,5.4463793547824545e9,7.074651672385337e8,2.595090695345872e8],0.3333333333333341),([-2.2418721864335723e9,2.4219211687208967e9,5.4463793547824545e9,7.074651672385337e8,2.595090695345872e8],0.3333333333333341)],9.474658864966518e-180)]

0 comments on commit 67b7808

Please sign in to comment.