Rename Distribution to MkDistribution

This commit is contained in:
Maciej Bendkowski 2022-03-27 11:45:18 +02:00
parent be03ce0fb3
commit 0dd5f40452
3 changed files with 7 additions and 7 deletions

View File

@ -102,7 +102,7 @@ instance EvalIO StdGen where
{-# INLINE evalIO #-}
evalIO m = eval m <$> getStdGen
newtype Distribution = Distribution {unDistribution :: Vector Int}
newtype Distribution = MkDistribution {unDistribution :: Vector Int}
deriving stock (Show)
deriveLift ''Distribution

View File

@ -21,7 +21,7 @@ import Language.Haskell.TH.Syntax (
)
import Control.Monad (foldM, forM, replicateM, unless)
import Data.Boltzmann.BuffonMachine (Distribution (Distribution))
import Data.Boltzmann.BuffonMachine (Distribution (MkDistribution))
import qualified Data.Map as Map
import Data.Map.Strict (Map)
import Data.Maybe (fromJust, fromMaybe)
@ -284,7 +284,7 @@ data Distributions a = Distributions
mkDidtributions :: Params -> Spec (Distributions a)
mkDidtributions params = do
let mkDistribution = Distribution . fromList . fromJust
let mkDistribution = MkDistribution . fromList . fromJust
regDdgs <- forM (Map.toList $ typeVariable params) $ \(name, v) -> do
ddgTree <- ddg v

View File

@ -46,18 +46,18 @@ choiceTests =
-- [1/2, 1/2]
distributionA :: Distribution
distributionA = Distribution $ fromList [2, 3, -2, -1]
distributionA = MkDistribution $ fromList [2, 3, -2, -1]
-- [1/3, 1/3, 1/3]
distributionB :: Distribution
distributionB = Distribution $ fromList [2, 138, 4, 137, 6, 133, 8, 132, 10, 128, 12, 127, 14, 123, 16, 122, 18, 118, 20, 117, 22, 113, 24, 112, 26, 108, 28, 107, 30, 103, 32, 102, 34, 98, 36, 97, 38, 93, 40, 92, 42, 88, 44, 87, 46, 83, 48, 82, 50, 78, 52, 77, 54, 73, 56, 72, 58, 68, 60, 67, 62, 66, 64, 65, -2, -1, -3, -3, 70, 71, -2, -1, -3, 75, 76, -2, -1, -3, 80, 81, -2, -1, -3, 85, 86, -2, -1, -3, 90, 91, -2, -1, -3, 95, 96, -2, -1, -3, 100, 101, -2, -1, -3, 105, 106, -2, -1, -3, 110, 111, -2, -1, -3, 115, 116, -2, -1, -3, 120, 121, -2, -1, -3, 125, 126, -2, -1, -3, 130, 131, -2, -1, -3, 135, 136, -2, -1, -3, 140, 141, -2, -1]
distributionB = MkDistribution $ fromList [2, 138, 4, 137, 6, 133, 8, 132, 10, 128, 12, 127, 14, 123, 16, 122, 18, 118, 20, 117, 22, 113, 24, 112, 26, 108, 28, 107, 30, 103, 32, 102, 34, 98, 36, 97, 38, 93, 40, 92, 42, 88, 44, 87, 46, 83, 48, 82, 50, 78, 52, 77, 54, 73, 56, 72, 58, 68, 60, 67, 62, 66, 64, 65, -2, -1, -3, -3, 70, 71, -2, -1, -3, 75, 76, -2, -1, -3, 80, 81, -2, -1, -3, 85, 86, -2, -1, -3, 90, 91, -2, -1, -3, 95, 96, -2, -1, -3, 100, 101, -2, -1, -3, 105, 106, -2, -1, -3, 110, 111, -2, -1, -3, 115, 116, -2, -1, -3, 120, 121, -2, -1, -3, 125, 126, -2, -1, -3, 130, 131, -2, -1, -3, 135, 136, -2, -1, -3, 140, 141, -2, -1]
-- [1/7, 4/7, 2/7]
distributionC :: Distribution
distributionC = Distribution $ fromList [2, 96, 4, 95, 6, 94, 8, 93, 10, 92, 12, 91, 14, 90, 16, 89, 18, 88, 20, 87, 22, 86, 24, 85, 26, 84, 28, 83, 30, 82, 32, 81, 34, 80, 36, 79, 38, 78, 40, 77, 42, 76, 44, 75, 46, 74, 48, 73, 50, 72, 52, 71, 54, 70, 56, 69, 58, 68, 60, 67, 62, 66, 64, 65, -3, -1, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2]
distributionC = MkDistribution $ fromList [2, 96, 4, 95, 6, 94, 8, 93, 10, 92, 12, 91, 14, 90, 16, 89, 18, 88, 20, 87, 22, 86, 24, 85, 26, 84, 28, 83, 30, 82, 32, 81, 34, 80, 36, 79, 38, 78, 40, 77, 42, 76, 44, 75, 46, 74, 48, 73, 50, 72, 52, 71, 54, 70, 56, 69, 58, 68, 60, 67, 62, 66, 64, 65, -3, -1, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2, -1, -3, -2]
distributionD :: Distribution
distributionD = Distribution $ fromList []
distributionD = MkDistribution $ fromList []
choiceTest :: Distribution -> Int -> IO [(Int, Double)]
choiceTest dist n = evalIO $ do