{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, UndecidableInstances #-} {-# OPTIONS_GHC -fno-warn-simplifiable-class-constraints #-} module Data.Random.Distribution.StretchedExponential where import Data.Random.RVar import Data.Random.Distribution import Data.Random.Distribution.Uniform newtype StretchedExponential a = StretchedExp (a,a) floatingStretchedExponential :: (Floating a, Distribution StdUniform a) => a -> a -> RVarT m a floatingStretchedExponential :: forall a (m :: * -> *). (Floating a, Distribution StdUniform a) => a -> a -> RVarT m a floatingStretchedExponential a beta a lambdaRecip = do a x <- forall a (m :: * -> *). Distribution StdUniform a => RVarT m a stdUniformT forall (m :: * -> *) a. Monad m => a -> m a return (forall a. Num a => a -> a negate (forall a. Floating a => a -> a log (a 1forall a. Num a => a -> a -> a -a x))forall a. Floating a => a -> a -> a **(a 1forall a. Fractional a => a -> a -> a /a beta) forall a. Num a => a -> a -> a * a lambdaRecip) floatingStretchedExponentialCDF :: Real a => a -> a -> a -> Double floatingStretchedExponentialCDF :: forall a. Real a => a -> a -> a -> Double floatingStretchedExponentialCDF a beta a lambdaRecip a x = Double 1 forall a. Num a => a -> a -> a - forall a. Floating a => a -> a exp (forall a. Num a => a -> a negate (forall a b. (Real a, Fractional b) => a -> b realToFrac a x forall a. Fractional a => a -> a -> a / forall a b. (Real a, Fractional b) => a -> b realToFrac a lambdaRecip)forall a. Floating a => a -> a -> a **(forall a b. (Real a, Fractional b) => a -> b realToFrac a beta)) stretchedExponential :: Distribution StretchedExponential a => a -> a -> RVar a stretchedExponential :: forall a. Distribution StretchedExponential a => a -> a -> RVar a stretchedExponential a beta a lambdaRecip = forall (d :: * -> *) t. Distribution d t => d t -> RVar t rvar forall a b. (a -> b) -> a -> b $ forall a. (a, a) -> StretchedExponential a StretchedExp (a beta, a lambdaRecip) stretchedExponentialT :: Distribution StretchedExponential a => a -> a -> RVarT m a stretchedExponentialT :: forall a (m :: * -> *). Distribution StretchedExponential a => a -> a -> RVarT m a stretchedExponentialT a beta a lambdaRecip = forall (d :: * -> *) t (n :: * -> *). Distribution d t => d t -> RVarT n t rvarT forall a b. (a -> b) -> a -> b $ forall a. (a, a) -> StretchedExponential a StretchedExp (a beta, a lambdaRecip) instance (Floating a, Distribution StdUniform a) => Distribution StretchedExponential a where rvarT :: forall (n :: * -> *). StretchedExponential a -> RVarT n a rvarT (StretchedExp (a beta,a lambdaRecip)) = forall a (m :: * -> *). (Floating a, Distribution StdUniform a) => a -> a -> RVarT m a floatingStretchedExponential a beta a lambdaRecip instance (Real a, Distribution StretchedExponential a) => CDF StretchedExponential a where cdf :: StretchedExponential a -> a -> Double cdf (StretchedExp (a beta,a lambdaRecip)) = forall a. Real a => a -> a -> a -> Double floatingStretchedExponentialCDF a beta a lambdaRecip