Proposal: Generalize the RandomGen and Random classes
Simon Peyton-Jones
simonpj at microsoft.com
Thu Oct 7 04:35:37 EDT 2010
| > RandomGen and Random classes assume generators produce Int values.
| > This is non-ideal as many high speed generators produce special values
| > (ex: doubles) or generic values (bit streams / bytestrings) that can
| > be converted directly to types easier than coercing to Int then to an
| > 'a' via the Random class.
On looking at this again, I think the proposed API looks over-elaborate. Surely there must be a better way?
The current design (trimmed down) is like this:
class RandomGen g where
next :: g -> (Int, g)
class Random a where
randoms :: forall g. RandomGen g => g -> [a]
The logic is
* RandomGen is a way to get a supply of bits, here expressed as Int
Maybe the class should have been called (BitSupply g)
* Random is a way to turn a supply of bits into values of some arbitrary type a
Notice that a single instance of Random, say Random Integer, will work for
*arbitrary* generators g.
In the proposal each instance of RandomGen produces values of a single type 'v', functionally dependent on the generator type 'g':
class RandomGen g v | g -> v where
next :: g -> (v, g)
Then there's a conversion from the fixed-but-unknown type 'v' to an arbitrary type 'a':
class Random a v where
randoms :: forall g. RandomGen g v => g -> [a]
The original message proposing the change omitted the 'v' parameter from Random. Yes, it's complicated: the intermediate type 'v' is really just a bit-supply.
Now we need to make a new instance of Random for each bit-supply type 'v'. It's not *so* bad: we expect to have
* Lots of generators g
* Lots of result types a
* Rather few bit-supply types v; perhaps just Int and Bytestring?
We need a Random instance for each (a,v) pair.
The types are a bit subtle. Look at the type of
randoms :: (Random a v, RandomGen g v) => g -> [a]
A call site presumably fixes, g and a; then the functional dependency fixes v; then we can find instances for (Random a v, RandomGen g v).
In type-function form it would have to look like this:
class RandomGen g where
type GenVal g :: *
next :: g -> (GenVal g, g)
class Random a v where
randoms :: forall g. (RandomGen g, v ~ GenVal g) => g -> [a]
which makes the functional dependency explicit.
It's not a silly design. But it's a rather abstract one, and there's always a danger of going overboard with abstraction in Haskell :-).
How many bit-supply types v do you want? Would it be enough to ask generators to generate all of them? Antoine suggested this:
class RandomGen g where
nextInt :: g -> (Int, g)
nextByteString :: g -> (ByteString, g)
But unlike Antoine's suggestion, I think we only need a tiny handful of bit supply types, because the Random class does the impedence matching to other types.
Simon
| -----Original Message-----
| From: libraries-bounces at haskell.org [mailto:libraries-bounces at haskell.org] On
| Behalf Of Thomas DuBuisson
| Sent: 06 October 2010 23:53
| To: Haskell Libraries; Milan Straka; Yitz
| Subject: Re: Proposal: Generalize the RandomGen and Random classes
|
| All,
| There has been precious few comments on this proposal (ending in 2
| days). Conversation has thus far been:
|
| Accept (1 - me)
| No - Random is H98 and changing it is not acceptable (2 - Milan, Yitz)
| Unknown Stance (2 - SPJ, Antonie Latter)
|
| Mostly I'm hoping for more comments. If you found the splittable
| debate of value then I'd imagine this aspect of Random would concern
| you too.
|
|
| In response to the idea that we can't or shouldn't change H98:
|
| Yitz:
| > If those extensions
| > are all added to Haskell 2011 or whatever, then it could be considered.
|
| AFAIK, all accepted parts of Haskell standards are implemented FIRST
| (typically as a GHC extension or package) then considered for
| Haskell'. The Haskell2010 and Haskell98 packages, which you can
| import, can contain their own definition of System.Random - this could
| be static without stagnating all libraries that are mentioned in a
| Haskell standard.
|
| Milan:
| > I personally do not think it is worth to modify the Random module, which
| > dates back to at least Haskell 98. Maybe a new package on the Hackage?
|
| So because it is old we can't modify it? The point of changing the
| library is to benefit a broader portion of the community. We could
| stop any and all changes to package X and make a new package every
| time but this isn't a sufficient argument to me.
|
| If peoples only objections are compatibility then we can queue this
| change up with the next API breaking change, unless there will never
| again be such a change.
|
| Cheers,
| Thomas
|
|
| On Tue, Sep 14, 2010 at 5:11 PM, Thomas DuBuisson
| <thomas.dubuisson at gmail.com> wrote:
| > Hello,
| > RandomGen and Random classes assume generators produce Int values.
| > This is non-ideal as many high speed generators produce special values
| > (ex: doubles) or generic values (bit streams / bytestrings) that can
| > be converted directly to types easier than coercing to Int then to an
| > 'a' via the Random class.
| >
| > See 4315 [1] for the patch.
| >
| > Period of discussion: Till October 8 (3.5 weeks, giving a little time
| > after ICFP for last minute debate)
| >
| > Specifically, this proposal:
| >
| > 1) Alters RandomGen:
| >
| > from:
| > class RandomGen g where
| > next :: g -> (Int, g)
| > genRange :: g -> (Int, Int)
| >
| > to
| >
| > class RandomGen g v | g -> v where
| > next :: g -> (v, g)
| > genRange :: g-> (v,v)
| >
| > 2) Alters Random:
| >
| > From:
| >
| > class Random a where
| > randomR :: RandomGen g => (a,a) -> g -> (a,g)
| > random :: RandomGen g => g -> (a, g)
| > randomRs :: RandomGen g => (a,a) -> g -> [a]
| > randoms :: RandomGen g => g -> [a]
| > randomRIO :: (a,a) -> IO a
| > randomIO :: IO a
| >
| > to
| >
| > class Random a where
| > randomR :: RandomGen g v => (a,a) -> g -> (a,g)
| > random :: RandomGen g v => g -> (a, g)
| > randomRs :: RandomGen g v => (a,a) -> g -> [a]
| > randoms :: RandomGen g v => g -> [a]
| >
| >
| > Additional Points of Debate
| > 1) Because random[R]IO can not be part of the new Random instance with
| > a sensible default, these have been moved to top-level functions:
| >
| > randomRIO :: (Random a Int) => (a,a) -> IO a
| > randomIO :: (Random a Int) => IO a
| >
| > Other options exist and I'm open to them. I'm just being upfront
| > about what the patch currently does.
| >
| > 2) All pre-existing instances of "Random x" for some concrete 'x' have
| > been modified to be "instance Random x Int". As 'Int' was the
| > previous (hardcoded) default for RandomGen this is simply matching the
| > behavior. More instances are possible and probably make sense now.
| > Alternatively, one could argue for zero default instance as they can
| > collide with how a particular user wishes types to be coerced.
| >
| > 3) Not-so-new extensions are used to enable these changes. Extensions
| > include MultiParamTypeClasses, FlexibleContexts, and FunDeps.
| >
| > 4) A patch is included bumping the version from 1.0.0.x to 1.1.0.0.
| >
| > Cheers,
| > Thomas
| >
| > [1] http://hackage.haskell.org/trac/ghc/ticket/4315
| >
| _______________________________________________
| Libraries mailing list
| Libraries at haskell.org
| http://www.haskell.org/mailman/listinfo/libraries
More information about the Libraries
mailing list