I'd like to have a function like:
unzipState :: (MonadState s m) => m (a, b) -> (m a, m b)
which would take a (stateful) computation that returns a tuple, and would return two (dependant) computations.
The difficulty is of course in that extracting values from one or the other computation should update the state in the other.
A useful (and motivating) application is the Random monad, expressed as
{-# LANGUAGE Rank2types #-}
import qualified System.Random as SR
import Control.Monad.State
type Random a = forall r. (State RandomGen r) => State r a
and let's say you have:
normal :: Random Double
-- implementation skipped
correlateWith :: Double -> Random (Double, Double) -> Random (Double, Double)
correlateWith rho w = do
(u, v) <- w
return $ (u, p * u + (1 - p * p) * v)
it would be quite natural to be able to write:
let x = normal
y = normal
(u, v) = unzipState $ correlateWith 0.5 $ liftM2 (,) x y
... now I am able to perform computation on u and v as correlated random variables
Is there a sensible way to do this ? I struggled a bit, but did not manage to get to anything. Hoogle was of no help either.
edit
Great answers have shown me my problem is ill-defined. Nevertheless, can someone explain me why the following implementation in python (which I believe to be correct, but have not tested much) cannot be translated in Haskell (with the magic of STrefs, closures and other things I admit I don't grasp ;-) ):
def unzipState(p):
flist, glist = [], []
def f(state):
if not flist:
(fvalue, gvalue), newstate = p(state)
glist.insert(0, gvalue)
return (fvalue, newstate)
else:
fvalue = flist.pop()
return (fvalue, state)
def g(state):
if not glist:
(fvalue, gvalue), newstate = p(state)
flist.insert(0, fvalue)
return (fvalue, newstate)
else:
gvalue = glist.pop()
return (gvalue, state)
return (f, g)
Not that I am saying that stateful code can be translated in Haskell, but I feel like understanding why and when (even on an example) it cannot be done would improve my understanding a lot.
edit2
Now it is crystal clear. The functons f and g are obviously not pure, as their output does not only depend on the value of state.
Thanks again !
The State Monad This context chains two operations together in an intuitive way. First, it determines what the state should be after the first operation. Then, it resolves the second operation with the new state. So for our Tic Tac Toe game, many of our functions will have a signature like State GameState a .
The state monad is a built in monad in Haskell that allows for chaining of a state variable (which may be arbitrarily complex) through a series of function calls, to simulate stateful code.
It's impossible to construct a general function unzipState
that does what you want, if only because you probably can't provide a formal specification for its intended effect. In other words, assume that you have implemented some function unzipState
. How do you know that it's correct? You would have to prove that it satisfies certain laws/equations, but the trouble here is to find these laws in the first place.
While I think I understand what you want to do, the Random
monad also makes it apparent why it cannot be done. To see that, you have to ditch the concrete implementation type Random a = ...
and consider the abstract interpretation given by
v :: Random a
means thatv
is a probability distribution of values of typea
The "bind" operation (>>=) :: Random a -> (a -> Random b) -> Random b
is simply a way to construct a new probability distribution from an old probability distribution.
Now, this means that unzipState
simply returns a pair of probability distributions, which can be used to construct other probability distributions. The point is that while the do
syntax looks very suggestive, but you don't actually sample random variables, you just calculate probability distributions. Random variables can be correlated, but probability distributions cannot.
Note that it is possible to create a different monad RandomVariable a
that corresponds to random variables. However, you have to fix the sample space Ω in advance. The implementation is
type RandomVariable a = Ω -> a
If you want both random variables and the ability to enlarge the sample space automatically, you probably need two bind operations
bind1 :: Random Ω a -> (a -> Random Ω b) -> Random Ω b
bind2 :: Random Ω1 a -> (a -> Random Ω2 b) -> Random (Ω1,Ω2) b
and some dependent type magic to deal with the proliferation of products like (Ω1,(Ω2,Ω3))
.
I'm not entirely clear on how you'd like this to work--since correlateWith
operates on a tuple, what meaning would the correlated variables have independently? Say you do this:
let x = normal
y = normal
(u, v) = unzipState $ correlateWith 0.5 $ liftM2 (,) x y
in do u1 <- u
v1 <- v
u2 <- u
u3 <- u
-- etc...
What relationship should exist between u1
, u2
, and u3
?
Also, a "random variable" like this can be converted into an infinite lazy stream in a straightforward fashion. What would the meaning of the following be?
let x = normal
y = normal
(u, v) = unzipState $ correlateWith 0.5 $ liftM2 (,) x y
in do vs <- generateStream v
u1 <- u
if someCondition u1 then u else return u1
-- etc...
Because the number of values sampled from u
changes based on u1
, this seems to suggest that the non-monadic value bound to vs
would retroactively depend somehow on u1
as well, which sounds suspiciously like the sort of spooky action at a distance that Haskell avoids.
I would hazard a guess that what you're trying to accomplish can't simply be retrofitted on top of a simple PRNG state monad, but there may be other options.
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With