[Haskell-cafe] ANN: random-fu 0.1.0.0

mokus at deepbondi.net mokus at deepbondi.net
Thu Jun 3 22:08:36 EDT 2010


> There's something in that package that I don't understand,
> and I feel really stupid about this.
>
> data RVarT m a
>
> type RVar = RVarT Identity
>
> class Distribution d t where
>      rvar :: d t -> RVar t
>      rvarT :: d t -> RVarT n t
>
> Where does "n" come from?
>

There's no reason to feel stupid when faced with something unfamiliar. 
Even if you are familiar with monad transformers, this may not be a place
you expect to find them, and 'n' in this case would usually be an 'm' in
other places (it is the underlying monad being extended).  Since I'm not
sure at which level your unfamiliarity lies, I'll just give a from-scratch
crash course.  Feel free to ignore as much as is necessary, and please
don't take this long-winded reply as any sort of condescension :).  I'll
refrain from introducing monads and monad transformers, as the internet is
already full enough of those sorts of introductions.

RVarT is a monad transformer that adds a source of "random" data to a
preexisting monad, the latter being the role the 'n' serves in rvarT's
type.  RVar is just the "pure" version where the underlying monad
(Identity) is sort of a type-level no-op.  With that background in mind,
the 2 methods of Distribution, rvar and rvarT, are exactly equivalent,
just specialized so that the compiler can avoid unnecessary conversions in
some cases.  The types are even isomorphic, I believe, due to
parametricity.

Both methods take the distribution in question (the "d t") and make an
"RVarT n t" that has that distribution (RVar is RVarT Identity, so n ==
Identity).  The reason the type variable is 'n' instead of 'm' as is more
traditional is related to the types of the function runRVarT and similar
functions for sampling the RVars:

> runRVarT :: (Lift  n m, RandomSource  m s) => RVarT  n a -> s -> m a

This involves 2 monads, and 'n' was used for the second of them.  For
consistency, 'n' is often used as the name of the corresponding variable
in type signatures using RVarT.  In runRVarT's type, 'n' is the monad
underlying the random variable and 'm' is the monad in which it is being
sampled.  They are allowed to differ so that random variables can be given
more general types.  If they had to be the same, the RVar would have to
carry around the monad in which it would eventually be sampled (and would
incidentally be granted access to all its capabilities via
Control.Monad.Trans.lift, which would be undesirable).  It would also
restrict the monads in which the RVar could be sampled.  With this scheme,
one RVar/RVarT can be sampled in many monads if desired (and I have used
this ability more than once in real code).

Finally, some may still wonder why there is a monad transformer here at
all - a plain RVar would already be sampleable in any monad that can feed
it some random data.  Originally that's what the library had, but a kind
and perceptive contributor (Reiner Pope) rectified that.  As a result, the
same framework supports some really nifty tricks, most importantly the
ability to define random processes reusing all the existing definitions of
random variables.



More information about the Haskell-Cafe mailing list