module Data.Lambda.Random.System
(
Expr(..)
, System
, boltzmannSystem
, mixedBoltzmannSystem
, Sampler(..)
, boltzmannSampler
, rejectionSampler
) where
import Prelude hiding (abs)
import Data.Lambda ()
import Data.Lambda.Model
import Data.Lambda.Random.Oracle
import qualified Data.Lambda.Random.PlainSystem as P
data Expr a = Expr { abs :: a
, app :: a
, idx :: [a]
} deriving (Show)
type System a = [Expr a]
evalH :: (Floating a, Integral b)
=> Model b -> b -> a -> a
evalH m h z = (1z^^csqrt ((z^^c1)^^2
(4*z^^(a+d)*(z^^(b*h)1))/(z^^b1)))/(2*z^^d)
where (a,b,c,d) = weights m
evalI :: (Floating a, Integral b)
=> Model b -> b -> a -> a -> a
evalI m i p z = (1sqrt (14*z^^d*(p*z^^c
+(z^^a*(z^^(b*i)1))/(z^^b1))))/(2*z^^d)
where (a,b,c,d) = weights m
evalS :: (Floating a, Integral b)
=> Model b -> a -> a -> a
evalS m p z = (1sqrt (14*p*z^^(c+d)))/(2*z^^d)
where (_,_,c,d) = weights m
take' :: (Integral a)
=> a -> [b] -> [b]
take' 0 _ = []
take' n (x:xs) = x : take' (n1) xs
take' _ [] = error "Empty list!"
computeIdx :: (Floating a, Integral b)
=> Model b -> b -> a -> a -> [a]
computeIdx _ 0 _ _ = []
computeIdx m h z w = take' h $ map (/ w) idxSeq
where idxSeq = z^^a : next idxSeq
next (x:xs) = x * z^^b : next xs
next _ = error "Finite list!"
(a,b,_,_) = weights m
boltzmannSystem :: (Floating a, Integral b)
=> Model b
-> b
-> a
-> System a
boltzmannSystem m h z = map toProb sys
where sys = snd $ computeSys' (evalH m h) m h 0 z
mixedBoltzmannSystem :: (Floating a, Integral b)
=> Model b
-> b
-> a
-> System a
mixedBoltzmannSystem m h z = map toProb sys
where sys = snd $ computeSys' (P.eval m) m h 0 z
computeSys' :: (Floating a, Integral b)
=> (a -> a) -> Model b -> b -> b -> a
-> (a, System a)
computeSys' eval m h i z
| i == 0 = let
w = evalS m w' z
(_,_,c,d) = weights m
(w',c1) = computeSys' eval m h 1 z
in (w, Expr { abs = (w' * z^^c) / w
, app = w * z^^d
, idx = computeIdx m 0 z w
} : c1)
| i == h = let
w = eval z
(_,_,c,d) = weights m
in (w, [Expr { abs = z^^c
, app = w * z^^d
, idx = computeIdx m h z w
}])
| otherwise = let
w = evalI m i w' z
(_,_,c,d) = weights m
(w',cp) = computeSys' eval m h (i+1) z
in (w, Expr { abs = (w' * z^^c) / w
, app = w * z^^d
, idx = computeIdx m i z w
} : cp)
toProbIdx :: (Num a)
=> a -> [a] -> [a]
toProbIdx _ [] = []
toProbIdx w (x:xs) = w' : toProbIdx w' xs
where w' = w + x
toProb :: (Num a)
=> Expr a -> Expr a
toProb expr = expr { app = x
, idx = idxs'
}
where app' = app expr
idxs' = toProbIdx x (idx expr)
x = abs expr + app'
data Sampler a b = Sampler { system :: System a
, model :: Model b
}
boltzmannSampler :: (Floating a, Integral b)
=> Model b
-> b
-> a
-> Sampler a b
boltzmannSampler m h z = let sys = boltzmannSystem m h z in
Sampler { system = sys
, model = m
}
rejectionSampler :: (Floating a, Ord a, Integral b)
=> Model b
-> b
-> a
-> Sampler a b
rejectionSampler m h eps = boltzmannSampler m h rho
where rho = domSingH m h eps