Re: [Haskell-cafe] Fun with the ST monad

2011-02-25 Thread mokus
On Fri, February 25, 2011 11:24 am, Andrew Coppin wrote:
 On 25/02/2011 02:16 AM, wren ng thornton wrote:

  Or
  converting the whole thing to an iteratee-style computation which is
  more explicit about the type of stream processing involved and thus what
  kinds of laziness are possible.

 I've heard much about this iteratee things, but I've never looked into
 what the hell it actually is.

 Today I had a look at TMR #16, which is an explanation which I can just
 about follow. It seems that it's actually a kind of fold - not unlike
 the streams of the stream-fusion library (which is something like what
 I thought I might end up needing). It seems to handle *input* very
 nicely, but I don't see much in the way of handling *output* well. (Then
 again, iteratee is just too complex to really comprehend properly.)

I also have had trouble digesting a lot of the literature on iteratees.  A
while back, I wrote up sort of a critique of/alternative to the current
presentations (largely for the self-enlightenment that comes from
wrestling with the concepts myself) and came up with a rather different
perspective on the subject.  I haven't previously shared it, because it's
extremely incomplete (especially the part about enumerators, which I was
about halfway through completely rewriting when I ran out of steam) and is
addressed to a very small (quite possibly non-existent) audience, but feel
free to take a look at it.  I've type-set the document in its current
state to a PDF at:

https://github.com/mokus0/junkbox/blob/master/Papers/HighLevelIteratees/HighLevelIteratees.pdf

This very well may do more to cloud the issue than clarify, and if so I'm
sorry - feel free to disregard me ;)

The short version is that I think there is a more enlightening view of
iteratees than as a kind of a fold.  For me, it makes a lot more sense to
think of them as operations in a particular abstract monad which has one
associated operation, a blocking read.  Under that view, it is also very
easy to extend them in arbitrary directions, such as adding support for
incremental output.

In any case, regarding your original question - I think iteratees are not
the right tool, if for no other reason than that the current
implementations are in my opinion far too brain-bending to use, especially
when it comes to enumeratees which is what you probably need.  Lazy ST
should fit the bill, though.  It works just like normal ST, but acts as if
every bind has 'unsafeInterleaveST'.  There's a good chance that just
changing the imports on your existing code (Control.Monad.ST -
Control.Monad.ST.Lazy, Data.STRef - Data.STRef.Lazy, etc.) will make it
work.

-- James


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functor = Applicative = Monad

2010-12-23 Thread mokus
On 22/12/2010 19:03, Simon Marlow wrote:
 On 14/12/2010 08:35, Isaac Dupree wrote:
 On 12/14/10 03:13, John Smith wrote:
 I would like to formally propose that Monad become a subclass of
 Applicative, with a call for consensus by 1 February. The change is
 described on the wiki at
 http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal,

 That page isn't written as a proposal yet, it's written as a bunch of
 ideas. I would be happy to see something along the lines of Bas van
 Dijk's work
 http://permalink.gmane.org/gmane.comp.lang.haskell.libraries/14740 .

 This is a proposal with far-reaching consequences, and with several
 alternative designs. I'm not sure I understand all
 the tradeoffs. Some parts of the proposal are orthogonal to the rest
 (e.g. changing fmap to map), and should probably be
 considered separately.

 Could someone please write a detailed proposal, enumerating all the
 pros and cons, and the rationale for this design
 compared to other designs?

 Cheers,
 Simon

I don't know exactly what the proposal process is, but what I'd like to
see is something like the following:

1)  Subclasses may declare default implementations of inherited methods. 
For example:

   class Functor f = Applicative f where
   ...
   fmap f x = pure f * x

   class Applicative f = Monad f where
   ...
   pure = return
   (*) = ap

2)  Unless superclass instances are already in scope at declaration of an
instance,  an instance declaration implicitly also declares the superclass
(and may also explicitly define functions in the superclass).  For
example:

   instance Monad Maybe where
   return = Just
   (=) = ...
   fmap = ...

This declaration, in the absence of any explicit instance Functor Maybe
and instance Applicative Maybe, would implicitly define those instances
as well, with the default implementations of fmap, pure, and * given.

It would be a compile-time error to inherit multiple default definitions
of a method, unless:
a) There is a clear shadowing (eg, if the Monad class declaration
included a default fmap, that would take precedence over the one in
Applicative)
b) The instance declaration explicitly defines the function, thus
resolving the conflict.

These changes, I believe, would make it possible to restructure the
heirarchy with negligible impact on user code.  The only potential impact
I see so far would have to involve orphan instances, which are already
considered risky/not a good idea.  Specifically, if there were already an
orphan Monad instance in one place and an orphan Applicative instance in
another, the orphaned Applicative instance would become a duplicate
instance which could potentially bite an end-user importing both modules.

It would also be possible with fairly small user impact to move 'return'
to Applicative, or even to a new 'Pointed' superclass of Applicative.  To
the end user, the type 'return :: Monad m = a - m a' would still be
valid, as would including return in a Monad instance declaration. 
Including 'pure' as well in Applicative (with defaults pure = return,
return = pure) would allow old Applicative declarations to continue to
work unchanged as well,  though that obviously has the downside of
introducing a new recursive default which is always potentially confusing
to writers of new instances.

-- James

PS. Incidentally, I'd also prefer a class like the following instead of
Applicative as it is now:
   class Functor f = Monoidal f where
   return :: a - f a
   (*)  :: f a - f b - f (a,b)

But that would be a much more disruptive change.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread mokus

 On 11 Aug 2010, at 14:17, Ertugrul Soeylemez wrote:

 There is a fundamental difference between an IO computation's result and
 a Haskell function's result.  The IO computation is simply a value, not
 a function.

 That's a rather odd distinction to make – a function is simply a value in
 a functional programming language.  You're simply wrapping up we're
 talking about haskell functions when we talk about referential
 transparency, not about IO actions in a way that maintains the warm fuzzy
 feeling.

 Bob

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


I don't know whether anyone is calling the execution of IO actions pure -
I would not, at any rate.  At some level, things MUST 'execute', or why
are we programming at all?  Philosophical points aside, there is still a
meaningful distinction between evaluating and executing a monadic action. 
While execution may not be pure, evaluation always is - and in the
examples given so far in this thread, there is (trivial) evaluation
occurring, which is the pure part that people have been referring to
(while ignoring the impure execution aspect).  Consider a variation on the
random integer theme, where the evaluation stage is made non-trivial. 
Assuming existence of some functions randomElement and greet of suitable
types:

 main = do
 putStr What names do you go by (separate them by spaces)? 
 names - fmap words getLine
 greetRandomName names

 greetRandomName [] = putStrLn Hello there!
 greetRandomName names = randomElement names = greet

The result of _evaluating_ greetRandomName name is either @putStrLn
Hello there!@ or @randomElement names = greet@, depending whether the
input list is empty.  This result absolutely can be substituted for the
original expression and potentially further pre-evaluated if names is a
known quantity, without changing the meaning of the program.  And, to
address an idea brought up elsewhere in this thread, it is absolutely true
as pointed out before that given the right (monadic) perspective a C
program shares exactly the same properties.

There is real additional purity in Haskell's case though, and it has
absolutely nothing to do with hand-waving about whether IO is pure, very
pure, extra-super-distilled-mountain-spring-water pure, or anything like
that.  As you rightly point out, executing IO actions at run-time is not
pure at all, and we don't want it to be.  The difference is that while in
Haskell you still have an IO monad that does what C does (if you look at C
in that way), you also have a pure component of the language that can be
(and regularly is, though people often don't realize it) freely mixed with
it.  The monadic exists within the pure and the pure within the monadic. 
'greetRandomName' is a pure function that returns an IO action.  That's
not hand-waving or warm fuzzies, it's fact.  greetRandomName always
returns the same action for the same inputs.  The same distinction is
present in every monad, although in monads that are already pure, such as
Maybe, [], Cont, etc., it's not as big a deal.

The mixture is not as free as some would like; the fact that Haskell has
this distinction between monadic actions and pure values (and the fact
that the former can be manipulated as an instance of the latter) means
that the programmer must specify whether to evaluate (=) or execute
(-) an action, which is a source of endless confusion for beginners and
debate over what pure means.  I don't expect I'll put an end to either,
but I would like to point out anyway that, if you accept that distinction
(the reality of which is attested by the existence of a computable
function - the type checker - for making the distinction), it's fairly
easy to see that evaluation is always pure, excepting abuse of
unsafePerformIO, et al., and execution is not.  Both occur in the context
of do-notation.  Functions returning monadic actions (whether the
resulting action is being evaluated or executed) are still always
evaluated to yield an action.  That evaluation is pure.  The execution of
the action yielded may not be, nor should it have to be - that's the whole
point of IO!  But we still have as much purity as is actually possible,
because we know exactly where _execution_ occurs and we don't pretend it
doesn't by confusing definition with assignment.  = always means = in
Haskell, and - doesn't.  In C, = always means -, even when the RHS
is a simple variable reference (consider x = x;).

-- James

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wildly off-topic: de Boor's algorithm

2010-08-06 Thread mokus
mo...@deepbondi.net wrote:
 It took me a while to get the intuition right on those, but here's a quick
 sketch.  Let n = number of control points, m = number of knots, and p =
 degree.  For p = 0 (constant segments), each control point corresponds to
 one span of the knot vector, so n = m - 1.  Each time you move up a
 degree, the basis functions span one more segment of the knot vector.
 Thus, to keep the same number of control points you have to add a knot
 when you add a degree, so n = m - 1 + p.  Equivalently, n - p = m - 1,
 which incidentally makes an appearance in the deBoor function below when
 we zip spans p us with spans 1 ds.  This is just the property that
 ensures that  the length of these lists is equal.

How embarrassing, I managed to get this simple math wrong.  That's what I
get for trying to think in the morning without either my notes or my
coffee, I suppose.  At least, I have that standard excuse to fall back on,
so I'll take advantage of it.  n = m - 1 + p should read n + p = m - 1
- I added p to the wrong side.

It is indeed the property that makes the zip line up, but not by the math
I gave.  Instantiating n and m as the respective length expressions
makes the equation:

 length ds + p = length us - 1

With subsequent derivation in light of the fact that the 1st control point
is being ignored (which introduces a - 1 on the RHS, if I'm not mistaken
again), as mentioned earlier, and the fact that the expression in question
is supposed to return a list one shorter than ds:

 length ds + p - 1 = length us - 1 = length (tail us)
 length ds - 1 = length (tail us) - p
 length (spans 1 ds) = length (spans p (tail us))

(Under the assumption that all the lists involved are long enough for the
tail and drop operations)
And all is (hopefully) right again.

-- James


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] can Haskell do everyting as we want?

2010-08-05 Thread mokus
David Leimbach wrote:
 On Wed, Aug 4, 2010 at 3:16 AM, Alberto G. Corona
 agocor...@gmail.comwrote:

 Just to clarify,  I mean: Haskell may be seriously addictive.  Sounds
 like
 a joke, but it is not.  I do not recommend it for coding something quick
 and
 dirty.


 I use it for quick and dirty stuff all the time, mainly because what I
 want
 is often something that can be broken down into stages of processing, and
 pure functions are really nice for that.

 If I know the input is coming from a reliable enough stream (like a unix
 pipe to stdin) I can use functions like interact to create filters, or
 parse some input, and produce some output.

 It's pretty nice.


I may be mistaken (in which case, I'm sorry for putting words in his
mouth) but I understood what he was saying not as that Haskell is not
suited for quick and dirty projects, but rather that Haskell for small
projects could be a dangerous gateway drug that could seriously impact
one's ability to continue to enjoy working in other languages.

-- James

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wildly off-topic: de Boor's algorithm

2010-07-24 Thread mokus
Andrew Coppin wrote:
 Given a suitable definition for Vector2 (i.e., a 2D vector with the
 appropriate classes), it is delightfully trivial to implement de
 Casteljau's algorithm:

 de_Casteljau :: Scalar - [Vector2] - [[Vector2]]
 de_Casteljau t [p] = [[p]]
 de_Casteljau t ps = ps : de_Casteljau t (zipWith (line t) ps (tail ps))

 line :: Scalar - Vector2 - Vector2 - Vector2
 line t a b = (1-t) *| a + t *| b

 Now if you want to compute a given point along a Bezier spline, you can do

 bezier :: Scalar - [Vector2] - Vector2
 bezier t ps = head $ last $ de_Casteljau t ps

 You can chop one in half with

 split :: Scalar - [Vector2] - ([Vector2], [Vector2])
 split t ps =
   let pss = de_Casteljau t ps
   in (map head pss, map last pss)

 And any other beautiful incantations.


 Now, de Boor's algorithm is a generalisation of de Casteljau's
 algorithm. It draws B-splines instead of Bezier-splines (since B-splines
 generalise Bezier-splines). But I think I may have ACTUALLY MELTED MY
 BRAIN attempting to comprehend it. Can anybody supply a straightforward
 Haskell implementation?

It took me a while to get around to it, and another while to work it out,
but here's what I've come up with.  First, here's a restatement of your
code with a concrete choice of types (using Data.VectorSpace from the
vector-space package) and a few minor stylistic changes just so things
will line up with the generalized version better:

  import Data.VectorSpace
 
  interp a x y = lerp x y a
 
  deCasteljau [] t = []
  deCasteljau ps t = ps : deCasteljau (zipWith (interp t) ps (tail ps)) t
 
  bezier ps = head . last . deCasteljau ps
 
  split ps t = (map head pss, reverse (map last pss))
  where pss = deCasteljau ps t

To generalize to De Boor's algorithm, the primary change is the
interpolation operation.  In De Casteljau's algorithm, every interpolation
is over the same fixed interval 0 = x = 1.  For De Boor's algorithm we
need a more general linear interpolation on the arbitrary interval
[x0,x1], because all the interpolations in De Boor's recurrence are
between pairs of knots, which have arbitrary values instead of just 0 or
1.

Because of Haskell's laziness, we can also take care of searching the
result table for the correct set of control points at the same time, just
by clamping the input to the desired interval and pre-emptively returning
the corresponding 'y' if the input is outside that interval.  This way, to
find the final interpolant we only need to go to the end of the table, as
in 'deCasteljau'.  Unlike 'deCasteljau', only a portion of the table is
actually computed (a triangular portion with the active control points as
base and a path from the vertex of the triangle to the final entry in the
table).

 interp x (x0,x1) (y0,y1)
 |  x   x0  = y0
 |  x = x1  = y1
 | otherwise = lerp y0 y1 a
 where
 a = (x - x0) / (x1 - x0)

Computing the table is now nearly as straightforward as in De Casteljau's
algorithm:

 deBoor p  _ [] x = []
 deBoor p (_:us) ds x = ds : deBoor (p-1) us ds' x
 where
 ds' = zipWith (interp x) (spans p us) (spans 1 ds)

Making use of a simple list function to select the spans:

 spans n xs = zip xs (drop n xs)

Note that the algorithm does not make use of @us!!0@ at all.  I believe
this is correct, based both on the Wikipedia description of the algorithm
and the implementations I've seen.  De Boor's recurrence seems to require
an irrelevant choice of extra control point that would be, notionally,
@ds!!(-1)@.  This control point has no actual influence inside the domain
of the spline, although it /can/ affect values outside the domain (The
domain being taken as the central portion of the knot vector where there
are @p+1@ non-zero basis functions, forming a complete basis for the
degree @p@ polynomials on that interval).

This implementation makes the arbitrary but justifiable choice that the
extra control point be identical to the first, so that the position of the
first knot is irrelevant. It could alternatively be written to take the
extra control point as an argument or as a part of @ds@, in which case the
caller would be required to supply an additional control point that does
not actually influence the spline.

I initially found this result difficult to convince myself of even though
it seems very plausible mathematically, because it seems to indicate that
in general the position of the first and last knots are utterly irrelevant
and I never saw any remarks to that effect in any of my reading on
B-splines. Empirically, though, it seems to hold.  Moving an internal knot
at one end of a basis function does not alter the shape of that function
in the segment furthest opposite, which is basically the same effect the
first knot should have on the first basis function (and the opposite
segment is the only one that falls inside the domain of the spline).  It
still may be that I'm wrong, and if anyone knows I'd love to hear about
it, but I'm presently inclined 

[Haskell-cafe] ANN: random-fu 0.1.0.0

2010-06-03 Thread mokus
Announcing the 0.1.0.0 release of the random-fu library for random
number generation[1].   This release hopefully stabilizes the core
interfaces (those exported from the base module Data.Random).

Warning to anyone upgrading from earlier releases: 'Discrete' has been
renamed 'Categorical', the entropy source classes have been redesigned,
and many things are no longer exported from the root module Data.Random
(In particular, DevRandom - this is not available on windows, so it will
likely move to its own package eventually so that client code dependencies
on it will be made explicit).

Unfortunately, Hackage appears to have choked on some of the package's
dependencies (specifically, 2 dependencies also depend on time, and were
built using different versions)  so its documentation (which I put quite a
bit of work into) is not displayed on the Hackage site.  In the past I
have dealt with that by uploading new versions with hacks to make sure the
thing builds, but I really would rather not continue to do so.  Is there
any procedure by which I can request a manual rebuild of the package so
that its documentation will be generated and displayed?

Incidentally, this is a recurring problem I have run into several times
for several packages.  Can we *please* come up with a way for sdist or
similar to just include pre-built documentation?  Or if I were to spend
some time working on such a thing, would it be accepted (assuming it was
done up to all applicable standards of quality)?

For now, I have added some pre-built haddock docs to the repository so
that they may be browsed online[2] (if code.haskell.org ever starts
responding to my HTTP requests.  It's just not my day today, I guess).

[1] http://hackage.haskell.org/package/random-fu-0.1.0.0
[2] http://code.haskell.org/~mokus/random-fu/doc/haddock/index.html

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Re: Difference between div and /

2010-06-03 Thread mokus

 On Thu, 3 Jun 2010, Maciej Piechotka wrote:

 Hmm. Thanks - however I fail to figure out how to do something like:

 generate a random number with normal distribution with average avg and
 standard deviation stdev.

 Unfortunately the package is restricted to discrete distributions so far.

Shameless self-advertisement: The random-fu package (whimsically named,
sorry) implements a modest variety of continuous distributions with what I
believe to be a user-friendly and flexible interface.

This thread inspired me to finish up and upload the 0.1 release (just
announced on haskell-cafe as well).  The public interface is slightly
different from earlier releases and the haddock docs for the new one
failed to build on hackage, but earlier versions have essentially the same
end-user interface aside from some changes in the module export lists so
if you'd like to get an idea of the basic spirit of the system you can
browse the docs for the earlier releases.  Alternatively, feel free to
browse the source and steal some of the implementations (many of which
were, in turn, translated from other sources such as wikipedia or the
Numerical Recipes book).

Unfortunately, the old documentation is much sparser and terser than the
new documentation that failed to build, but if nothing else you can
download and build the docs yourself for the new one.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: random-fu 0.1.0.0

2010-06-03 Thread mokus
 The only feature suggestion I can suggest is the addition of a
 convolution operator to combine distributions (reified as RVar's in
 this implementation, though of course the difference between a random
 variable over a distribution and the distribution is rather thin)

I don't think I understand.  My familiarity with probability theory is
fairly light.  Are you referring to the fact that the PDF of the sum of
random variables is the convolution of their PDFs?  If so, the sum of
random variables can already be computed as liftA2 (+) :: Num a = RVar a
- RVar a - RVar a since RVar is an applicative functor (or using liftM2
since it's also a monad).

Or perhaps you mean an operator that would take, say, 2 values of the
'Uniform' data type and return an instance of the 'Triangular' type
corresponding to the convolution of the distributions?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: random-fu 0.1.0.0

2010-06-03 Thread mokus

 On the other hand, it might be kind of nice if RVar's knew which PDF
 they are over.  It's hard for me to see how that would be done with
 Haskell.

If anyone knows a way this could be done while still allowing general
functions to be mapped over RVars, I'd love to hear about it.  My
suspicion though is that it is not possible.  It would be a very similar
problem to computing the inverse of a function since the PDF is a measure
of the size of the preimage of an event in the probability space (if I'm
putting all those words together correctly ;)).

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: random-fu 0.1.0.0

2010-06-03 Thread mokus
 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.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: True Random Numbers

2010-04-08 Thread mokus
 Is there a way to get multiple random numbers without having to
 replicateM?

 While comparing the random-fu interface with Control.Monad.Random (both
 using StdGen), I noticed that while performance is comparable, using
 getRandomRs to get a list of random numbers is a lot faster than
 replicating uniform (or getRandomR for that matter). I don't know if
 this kind of speed gain makes sense for random-fu though.

I have been attempting to replicate this.  What sort of a performance
difference are you seeing, and are you using the hackage-released version
of random-fu or the darcs one?  The darcs release is, overall, a fair bit
faster than the current hackage release.  Depending on the particular way
that I sample my RVars (eg, replicateM n (sample ...) vs sample
(replicateM n ...)), I am seeing the random-fu version of my little
benchmark run anywhere from 30% faster to 25% slower than
Control.Monad.Random.getRandomRs (for 64000 uniform Double samples).  The
same benchmark using random-fu-0.0.3.2 shows it consistently about 33%
slower than getRandomRs.

In case you're interested, this is the (criterion) benchmark I used (with
count = 64000, and in the first bgroup 'src' is an IORef StdGen):

 [ bgroup replicateM
 [ bench randomRIO $ do
 xs - replicateM count (randomRIO (10,50) :: IO Double)
 sum xs `seq` return ()

 , bench uniform A $ do
 xs - replicateM count
   (sampleFrom src (uniform 10 50) :: IO Double)
 sum xs `seq` return ()
 , bench uniform B $ do
 xs - sampleFrom src
   (replicateM count (uniform 10 50)) :: IO [Double]
 sum xs `seq` return ()
 ]

 , bgroup pure StdGen
 [ bench getRandomRs $ do
 src - newStdGen
 let (xs, _) = CMR.runRand (CMR.getRandomRs (10,50)) src
 sum (take count xs :: [Double]) `seq` return ()
 , bench RVarT, State - sample replicateM $ do
 src - newStdGen
 let (xs, _) = runState
   (sample (replicateM count (uniform 10 50))) src
 sum (xs :: [Double]) `seq` return ()
 , bench RVarT, State - replicateM sample $ do
 src - newStdGen
 let (xs, _) = runState
   (replicateM count (sample (uniform 10 50))) src
 sum (xs :: [Double]) `seq` return ()
 ]

If the problem is worse than this benchmark indicates, or if this
benchmark shows radically different results on a different platform (I'm
running on Mac  OS 10.6 with GHC 6.12.1), I'd love to hear about it.  I
could certainly imagine cases where the choice of monad in which to sample
makes things quite slow.  In the above case, I was using IO in the first
bgroup and State StdGen in the second.

As for whether an optimization like getRandomRs would benefit the
random-fu library:  I have tried a few different times to implement list
or vector primitives and the corresponding high-level interfaces for
sampling many variables at once, but have not yet come up with a version
that actually made anything faster.  I'm more than happy to accept patches
if someone comes up with one, though! ;)

-- James

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe