[Haskell-cafe] Explicit approach to lazy effects For probability monad?

Benjamin Redelings benjamin.redelings at gmail.com
Thu Nov 7 16:56:52 UTC 2019


Hi Olaf,

Thanks for your reply!  I think I was unclear about a few things:

1. Mainly, I am _assuming_ that you can implement a lazy probability 
monad while ignoring random number generators.  So, monad should be 
commutative, and should have the second property of laziness that you 
mention.

(As an aside, I think the normal way to do this is to implement a 
function that splits the random number generator whenever you perform a 
lazy random computation using function: split :: g -> (g,g).  My hack is 
to present that we have a hardware instruction that generates true 
random numbers, and then put that in the IO Monad, and then use 
unsafeInterLeaveIO.  However, I would have to think more about this.)

2. My question is really about how you can represent side effects in a 
lazy context.  Thus the monad would be something like

EffectMonad = (a, Set Effect),

where Effect is some ADT that represents effects.  Each effect 
represents some action that can be undone, such as registering a newly 
created random variable in the list of all random variables.

This seems to be easy in a strict context, because you can change a 
function a->b that has effects into a-> EffectMonad b. Then your 
interpreter just needs to modify the global state to add the effects 
from the

interpreter state1 (x <<= y) = let (result1,effects1) = interpreter state1 x
                                   state2 = state1 `union` effects1
                                in interpreter state2 (y result1)

However, with a lazy language I think this does not work, because we do 
not want to include "effects1" unless the "result1" is actually consumed.

In that context, I think that a function (a->b) would end up becoming

EffectMonad a -> EffectMonad (EffectMonad b)

The argument 'a' changes to EffectMonad 'a' because the function itself 
(and not the interpreter) must decide whether to include the effects of 
the input into the effects of the output.  The output changes to 
EffectMonad (EffectMonad b) so that the result is still of type 
(EffectMonad b) after the result is unwrapped.

Does that make more sense?

-BenRI




On 10/17/19 4:03 PM, Olaf Klinke wrote:
> Hi Benjamin,
>
> Your example code seems to deal with two distinct types:
> The do-notation is about the effects monad (on the random number generator?) and the `sample` function pulls whatever representation you have for an actual probability distribution into this effect monad. In my mental model, the argument to `sample` represents a function Double -> x that interprets a number coming out of the standard random number generator as an element of type x.
> I suggest to consider the following two properties of the mathematical probability monad (a.k.a. the Giry monad), which I will use as syntactic re-write rules in your modeling language.
>
> The first property is Fubini's Theorem. In Haskell terms it says that for all f, a :: m x and b :: m y the two terms
>
> do {x <- a; y <- b; f x y}
> do {y <- b; x <- a; f x y}
>
> are semantically equivalent. (For state monads, this fails.) Monads where this holds are said to be commutative. If you have two urns, then drawing from the left and then drawing from the right is the same as first drawing from the right and then drawing from the left. Using Fubini, we can swap the first two lines in your example:
>
> model = do
>     cond <- bernoulli 0.5
>     x <- normal 0 1
>     return (if cond == 1 then x else 0)
>
> This desugars to
>
> bernoulli 0.5 >>= (\cond -> normal 0 1 >>= (\x -> return (if cond == 1 then x else return 0)))
> bernoulli 0.5 >>= (\cond -> fmap (\x -> if cond == 1 then x else 0) (normal 0 1))
>
> The second property is a kind of lazyness, namely
>
>      fmap (const x) and return are semantically equivalent.
>
> which holds for mathematical distributions (but not for state monads). Now one could argue that in case cond == 0 the innermost function is constant in x, in which case the whole thing does not depend on the argument (normal 0 1). The Lemma we need here is semantic equivalence of the following two lambda terms.
>
> \cond -> \x -> if cond == 1 then x else 0
> \cond -> if cond == 1 then id else const 0
>
> If the above is admissible then the following syntactic transformation is allowed:
>
> model = do
>     cond <- bernoulli 0.5
>     if cond == 1 then normal 0 1 else return 0
>
> which makes it obvious that the normal distribution is only sampled when needed. But I don't know whether you would regard this as the same model. Notice that I disregarded your `sample` function. That is, my monadic language is the monad of probabilites, not the monad of state transformations of a random number generator. Maybe you can delay using the random number generator until the very end? I don't know the complete set of operations your modeling language sports. If that delay is possible, then maybe you can use a monad that has the above two properties (e.g. a reader monad) and only feed the random numbers to the final model. As proof of concept, consider the following.
>
> type Model = Reader Double
> model :: Model Int
> model = do
>    x <- reader (\r -> last [1..round (recip r)])
>    cond <- reader (\r -> r > 0.5)
>    return (if cond then x else 0)
>
> runReader model is fast for very small inputs, which would not be the case when the first line was always evaluated.
>
> Cheers,
> Olaf
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20191107/d6978070/attachment.html>


More information about the Haskell-Cafe mailing list