Gentlefolk,

Haskell 98 is gettting there.  Draft version 3 of both Language and Library
Reports are on the Web now, along with an updated 'complete list of
changes'.

        http://research.microsoft.com/users/simonpj/Haskell/haskell98.html

I decided a few things I'd previously canvassed opinion about:
        - named-field syntax for newtype
        - leading underscore should suppress 'unused variable' warnings
        - monomorphism clarification

The only unresolved area so far as I know is the Random library.
An ad-hoc sub-group have been educating me in the ways of righteousness,
and we now have rather a nice design I think.  It's enclosed below,
but not yet included in the library report because I wanted to fly
it past the main list first.

Remember, the goal is to freeze the design by Christmas.  After that,
I'm going to call it 'Haskell 98 beta1' and deal with actual errors,
and typographical and presentational changes only.  (Experience proves
that there always are some.) 

Simon

===========================================================
module Random (
        RNG(nextRNG, splitRNG),
        StdRNG,

        Random( mkRandom, mkRandomR, mkRandoms, mkRandomRs,
                mkRandomIO, mkRandomRIO ),

        getRandomSupply, setRandomSupply, newRandomSupply,
        getRandomIO
  ) where
        
---------------- The RNG class ---------------------------

class RNG r where
  nextRNG :: r  -> (Int, r)
  splitRNG :: r -> (r, r)       -- May not exist for all RNGs


---------------- A standard instance of RNG ---------------
data StdRNG = ...       -- Abstract

instance RNG StdRNG where ...

instance Read StdRNG where ...
        -- read succeeds on *any* string, not only those
        -- constructed with show.  Hence you can use any
        -- string as way to construct a RandomSupply
 
instance Show StdRNG where ...


---------------- The Random class ---------------------------

class Random a where
   mkRandomR :: RNG s => (a, a) -> s -> (a, s)
        -- For discrete types, return a value in [lo,hi]
        -- For fractional types, return a value in [lo,hi)

   mkRandom  :: RNG s -> (a, s)
        -- Return any value of type a.
        -- For bounded types, the range is normally the whole type
        -- For Fractional types, the range is normally [0..1]
        -- For Integer, the range is (arbitrarily) the range of Int

   mkRandoms  :: RNG s => s -> [a]
   mkRandomRs :: RNG s => (a, a) -> s -> [a]

   mkRandomIO :: IO a
   mkRandomRIO :: (a,a) -> IO a

        -- Default methods
   mkRandoms s = x : mkRandoms s' 
                   where 
                     (x,s') = mkRandom s
   mkRandomRs = ...similar...

   mkRandomIO        = getRandomIO mkRandom
   mkRandomRIO range = getRandomIO (mkRandomR range)


instance Random Int     where ...
instance Random Integer where ...
instance Random Float   where ...
instance Random Double  where ...
instance Random Bool    where ...
instance Random Char    where ...


---------------- The global RNG ---------------------------

-- There is a single, implicit, global random number supply
-- of type StdRNG, held in some global variable maintained by the IO monad
--
-- It is initialised non-deterministically; to get
-- deterministic behaviour use setRandomSupply.

setRandomSupply :: StdRNG -> IO ()      -- Set the global supply
getRandomSupply :: IO StdRNG            -- Get the global supply

getRandomIO :: (StdRNG -> (a, StdRNG)) -> IO a
        -- Use the supplied function to get a value from
        -- the current global random supply, s, and update the
        -- global supply with the new supply returned
getRandomIO f = do
        s <- getRandomSupply
        let (val, s') = f s
        putRandomSupply s'
        return val

newRandomSupply :: IO StdRNG
        -- Apply splitRNG to the current global random
        -- supply, update it with one of the results and return the other
newRandomSupply = do
        s <- getRandomSupply
        let (s1,s2) = splitRNG s
        putRandomSupply s1
        return s2


Reply via email to