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

Benjamin Redelings benjamin.redelings at gmail.com
Wed Nov 13 16:58:59 UTC 2019


Hi Olaf,

Thanks for your interesting response!  Keep in mind that I have written 
my own Haskell interpreter, and that the lazy random monad is already 
working in my interpreter.  So I am seeing the issue with effects as 
second issue.

See http://www.bali-phy.org/models.php for some more information on this 
system.  Note that I also have 'mfix' working in the lazy random monad, 
which I think is pretty cool.  (See the second example about trait 
evolution on a random tree).  However, I have no type system at all at 
the present time.

On 11/10/19 4:21 PM, Olaf Klinke wrote:
> I believe that with the right monad, you won't need to think about side-effects, at least not the side-effects that are manual fiddling with registering variables. Haskell should do that for you.

So, I'm trying to implement a random walk on the space of Haskell 
program traces.  (A program trace records the execution graph to the 
extent that it depends on builtin operations with random results, such 
as sampling from a normal distribution.)  I could provide a PDF of an 
example execution trace, if you are interested.

This means that logically Haskell is kind of running at two levels:

(1) there is an inner random program that we are making a trace of.

(2) there is another outer program that modifies these traces.

The reason I think I need "registration" side-effects is that the outer 
program needs a list of random variables in the trace graph that it can 
randomly tweak.  For example, if the inner program is given by:

do
   x <- sample $ normal 0 1  ----- [1]
   observe (normal x 1) 10
   return $ log_all [x %% "x"]

then the idea is that "x" would get registered when it first accessed.  
This allows the outer program needs to know that it can modify the node 
for "x" in the trace graph.  This side-effect is invisible to the inner 
program, but visible to the outer program.

So, I'm not sure if it is correct that I would not need side-effects.  
However, if I could avoid side-effects, that would be great.

> It seems to me what you really need is a strictness analyzer together with the appropriate re-write rules that push the call to monadic actions as deep into the probabilistic model as possible. But initially you said you want to avoid source-to-source translations.

I think maybe you are right that source-to-source transforms are the 
right way.  Currently I have avoided by writing my own interpreter and 
virtual machine that keeps track of trace graphs.

What do you mean about pushing monadic actions as deep into the 
probabilistic model as possible?

> Indeed your mention of splitting the random number generator seems to buy laziness, judging by the documentation of MonadInterleave in the MonadRandom package. But looking at the definition of interleave for RandT you can see that the monadic computation is still executed, only the random number generator state is restored afterwards. In particular, side effects of the inner monad are always executed. (Or was I using it wrong?) Hence from what I've seen my judgement is that state transformer monads are a dead end.

Hmm... I will have to look at this.  Are you saying that in the 
MonadRandom package, interleaved computations are not sequenced just 
because of the random number generator, but they ARE sequenced if they 
perform any monadic actions?  If this is true, then it would seem that 
the state is not the problem?

In any case I think the problems that come from threading random number 
generator state are not fundamental.  There are machine instructions 
that generate true randomness, so one could always implement randomness 
in the IO monad without carrying around a state.

interpreter (f >>= g) = do
                            x <- unsafeInterleaveIO $ interpreter f
                            interpreter $ g x

I have a very hacky system, but this is basically what I am doing.  It 
is probably terrible, but I have not run into any problems so far.  Is 
there a reason that one should avoid this?

So far it seems to work.  I am not that worried about the probability monad.


> The idea with changing a -> m b to m a -> m (m b) seemed promising as well. You can easily make a Category instance for the type
>
> C a b = m a -> m (m b)
>
> so that composition of arrows in C does not necessarily execute the monadic computation. However, functions of the Arrow instance (e.g. 'first') must look at the input monad action in order to turn C a b into C (a,c) (b,c), at least I could not think of another way.

I'm sorry, I am not very familiar with the Haskell functions for 
categories, I just read part of Chapter 1 of an Algebraic Topology book.

Can you possibly rephrase this in terms of (very simple) math? 
Specifically, I was thinking that mapping (a->b) to (m a -> m (m b)) 
looks like a Functor where

a       =>  m a                           --- this is "return"

a->b =>  m a -> m (m b)        --- this is "fmap"

Why are you saying that this a category instead of a functor?  I am 
probably just confused, I am not very familiar with categories yet, and 
have not had time to go look at the Arrow instance you are talking about.

> Sorry for writing so destructive posts. In mathematics it is generally easier to find counterexamples than to write proofs.

Haha, no problem.  Its not clear to me that this is possible.  If in 
general lazy effects cannot be represented in Haskell using do-notation, 
that would probably be interesting to state formally.


-BenRI

[1] Regarding "sample", I think that if I I write "x <- normal 0 1" then 
I think that I cannot write "observe (normal x 1) 10", but would have to 
distinguish the distribution (normalDistr x 1) from the action of 
sampling from the distribution (normal 0 1). In my notation (normal x 1) 
is the distribution itself, and not an action.

But if I could eliminate the "sample" then I think the code would look a 
lot cleaner.


>
> Olaf
>   
>
>> Am 07.11.2019 um 17:56 schrieb Benjamin Redelings <benjamin.redelings at gmail.com>:
>>
>> 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/20191113/ba0a714a/attachment.html>


More information about the Haskell-Cafe mailing list