Re: bug in ghc-4.06 ?

2000-02-04 Thread Jeffrey R. Lewis

"S.D.Mechveliani" wrote:

 Dear GHC,

 I fear, there is some hard bug in  ghc-4.06.
 On the program

   main = let  p= 5 :: Integer
   iI   = eucIdeal "be" p [] [] [(p,1)]
   r1   = Rse 1 iI dZ
   dK   = upGCDRing r1 eFM
  --upRing
   setK = snd $ baseSet r1 dK
  in   putStr $ shows (osetCard setK) "\n"

 ghc-4.04 behaves correct,
 while  ghc-4.06  prints  "UnknownV"  instead of  "Fin 5".

 upGCDRing r1 eFM   applies   upRing r1 eFMand then adds to the
 result certain things.
 Replacing  upGCDRing  with  upRing  in the above `main' has to
 preserve the result. And  ghc-4.06  does not preserve it.

 If you want to debug this, tell me to what address to send this bug
 project - 100-300 Kbyte.

I'll pass, but I suspect I know what the bug is.

Consider this little program:


 class C awhere c :: a
 class C a = D a where d :: a

 instance C Int where c = 17
 instance D Int where d = 13

 instance C a = C [a] where c = [c]
 instance ({- C [a], -} D a) = D [a] where d = c

 instance C [Int] where c = [37]

 main = print (d :: [Int])

What do you think `main' prints  (assuming we have overlapping instances, and
all that turned on)?  Well, the instance for `D' at type `[a]' is defined to
be `c' at the same type, and we've got an instance of `C' at `[Int]', so the
answer is `[37]', right? (the generic `C [a]' instance shouldn't apply because
the `C [Int]' instance is more specific).

Ghc-4.04 gives `[37]', while ghc-4.06 gives `[17]', so 4.06 is wrong.  That
was easy ;-)  Let's just consult hugs for good measure.  Wait - if I use old
hugs (pre-September99), I get `[17]', and stranger yet, if I use hugs98, it
doesn't even compile!  What's going on!?

What hugs complains about is the `D [a]' instance decl.


 ERROR "mj.hs" (line 10): Cannot build superclass instance
 *** Instance: D [a]
 *** Context supplied: D a
 *** Required superclass : C [a]

You might wonder what hugs is complaining about.  It's saying that you need to
add `C [a]' to the context of the `D [a]' instance (as appears in comments).
But there's that `C [a]' instance decl one line above that says that I can
reduce the need for a `C [a]' instance to the need for a `C a' instance, and
in this case, I already have the necessary `C a' instance (since we have `D a'
explicitly in the context, and `C' is a superclass of `D').

Unfortunately, the above reasoning indicates a premature commitment to the
generic `C [a]' instance.  I.e., it prematurely rules out the more specific
instance `C [Int]'.  This is the mistake that ghc-4.06 makes.  The fix is to
add the context that hugs suggests (uncomment the `C [a]'), effectively
deferring the decision about which instance to use.

Now, interestingly enough, 4.04 has this same bug, but it's covered up in this
case by a little known `optimization' that was disabled in 4.06.  Ghc-4.04
silently inserts any missing superclass context into an instance declaration.
In this case, it silently inserts the `C [a]', and everything happens to work
out.

So, what's the fix?  I think hugs has it right (of course I do ;-).  Here's
why.  Let's try something else out with ghc-4.04.  Let's add the following
line:

d' :: D a = [a]
d' = c

Everyone raise their hand who thinks that `d :: [Int]' should give a different
answer from `d' :: [Int]'.  Well, in ghc-4.04, it does.  The `optimization'
only applies to instance decls, not to regular bindings, giving inconsistent
behavior.

What hugs does is this: like GHC, the list of instances for a given class is
ordered, so that more specific instances come before more generic ones.  For
example, the list might contain:
..., C Int, ..., C a, ...
When we go to look for a `C Int' instance we'll get that one first.  But what
if we go looking for a `C b' (`b' is unconstrained)?  We'll pass the `C Int'
instance, and keep going.  But if `b' is unconstrained, then we don't know yet
if the more specific instance will eventually apply.  GHC keeps going, and
matches on the generic `C a'.  Hugs, on the other hand, at each step, checks
to see if there's a reverse match, and if so, aborts the search.  This
prevents hugs from prematurely chosing a generic instance when a more specific
one may apply at some later point.

If y'all agree that GHC should match hugs on this, it's only about a 4 line
fix - I've tried it out already.  On the other hand, I don't think that this
will make Sergey a happy camper.  Many instance declarations need to be
tweaked.  It's a tedious job, but straightforward.

--Jeff




Re: parse error in Hugs98 library

2000-02-04 Thread Sven Panne

Nick Eby wrote:
 In trying to compile the Random library from the hugs98 distribution
 i got the following error:
 Random.hs:205: parse error on input `::'
 Line 205 reads:
 primitive getRandomSeed :: IO Integer
 
 I don't see a syntactic error in this line.

I do.   :-)

 Does ghc have a problem with the 'primitive' declaration? [...]

Exactly. In GHC (and probably already in NHC, too. Malcolm?) you
have to write

   foreign import unsafe getRandomSeed :: IO Int

A few remarks:

   * `unsafe' is not necessary, but improves performance, telling
 GHC that getRandomSeed won't re-enter Haskell-land before it
 has finished (less state to save/restore in the RTS).

   * You can't return `Integer' in GHC, only `Int'. This is a
 deliberate design decision, because only primitive types should
 be handled by the FFI. Integers are not primitive at all, see
 e.g. libgmp.

   * Obvious, but easily forgotten: Don't forget -fglasgow-exts and
 link with the object file containing getRandomSeed (which you
 probably have to rip off the Hugs98 sources).

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne



bug in 4.06 ?

2000-02-04 Thread S.D.Mechveliani

Some letter! Some investigation. Thank you, Jeffrey.

GHC, please, could you fix things? 
If only it is true ...
Indeed, the DoCon program uses overlapping and "undecidable" 
instances quite freely. The constructor Rse below is supplied with
the two overlapping instances in this bug project. The general program
adds one more. 
But everything worked, - in my practice, - in ghc-4.04, many tests were 
tried.

--
Sergey Mechveliani
[EMAIL PROTECTED]




04 Feb 2000   From: "Jeffrey R. Lewis" [EMAIL PROTECTED]
Subject: Re: bug in ghc-4.06 ?

   main = let  p= 5 :: Integer
  [..]
  in   putStr $ shows (osetCard setK) "\n"

 ghc-4.04 behaves correct,
 while  ghc-4.06  prints  "UnknownV"  instead of  "Fin 5".
 [..]
 If you want to debug this, tell me to what address to send this bug
 project - 100-300 Kbyte.


 I'll pass, but I suspect I know what the bug is.
 Consider this little program:

 class C awhere c :: a
 class C a = D a where d :: a
 [..]
 What do you think `main' prints  (assuming we have overlapping instances, and
 all that turned on)?  Well, the instance for `D' at type `[a]' is defined to
 be `c' at the same type, and we've got an instance of `C' at `[Int]', so the
 answer is `[37]', right? (the generic `C [a]' instance shouldn't apply because
 the `C [Int]' instance is more specific).

 Ghc-4.04 gives `[37]', while ghc-4.06 gives `[17]', so 4.06 is wrong. 
 [..]




Re: panic! (the `impossible' happened):

2000-02-04 Thread George Russell

Michael Weber wrote:
 
 On Wed, Feb 02, 2000 at 09:16:01 -0800, Simon Peyton-Jones wrote:
  | From: George Russell [mailto:[EMAIL PROTECTED]]
  | panic! (the `impossible' happened):
  | cgEvalAlts: dodgy case of unboxed tuple type
 [...]
 
  I'm unable to reproduce this.  It's a message from inside the code
  generator, but my freshly-checked out build of the head of the tree
  compiles fine.
 
 I was able to reproduce this bug by compiling with `-Onot' (4.06.2109):
 [550]$ make all EXTRA_HC_OPTS=-Onot
Well, I owe Michael Weber a drink at least for saving me the bother of trying
to reproduce the bug again with Simon PJ's changes, though if Simon PJ wants me
to try again I will.  However I didn't use -Onot.  build.mk (minus comments and
blank lines was):

HAPPY = /usr/local/pub-bkb/ghc/ghc-latest/bin/happy -a -g -c
GhcLibHcOpts += -H20m
HC_OPTS += -H30m -Onot
rename/ParseIface_HC_OPTS += -K5m -H80m -optCrts-M90m
parser/Parser_HC_OPTS += -K5m -H80m -optCrts-M90m
Time_HC_OPTS += -H40m
LALR_HC_OPTS += -H40m
GhcLibWays=

./configure was run --with-hc set to the latest (4.06) binary distribution
and --with-gcc set to gcc2.95.2 -m32.

I am using Sun's version of ar and ld, because that's what the installation
notes for GCC recommend.  

The GHC sources were downloaded from CVS a week ago on Friday afternoon.
It's still possible of course, since Simon PJ can't reproduce the problem,
that it has something to do with some flakiness in the interaction between
gcc2.95.2 and everything else.



RE: bug in ghc-4.06 ?

2000-02-04 Thread Simon Peyton-Jones


| If y'all agree that GHC should match hugs on this, it's only 
| about a 4 line
| fix - I've tried it out already.  On the other hand, I don't 
| think that this
| will make Sergey a happy camper.  Many instance declarations 
| need to be
| tweaked.  It's a tedious job, but straightforward.

I'd buy that, Jeff.  Unless anyone disagrees, why don't you go ahead
and make the change?  It may require tweaking of not only instance
decls but also ordinary decls with type signatures, right?  But only
for people who use overlapping instance decls.

When you make the fix, could you put the entire text of your message
in as a comment?  (Edit it if you like, of course, but don't remove
the examples.  I have slowly come to realise that whenever one makes
a 2-line fix motivated by a strange case one should put the strange
case in as a comment. I have often reversed such changes two years later
because I though they were bogus, only to rediscover the strange case...)

Simon



Re: panic! (the `impossible' happened):

2000-02-04 Thread Michael Weber

On Fri, Feb 04, 2000 at 11:27:19 +0100, George Russell wrote:
[...]
 However I didn't use -Onot.  build.mk (minus comments and blank lines was):
   ^
 HAPPY = /usr/local/pub-bkb/ghc/ghc-latest/bin/happy -a -g -c
 GhcLibHcOpts += -H20m
 HC_OPTS += -H30m -Onot
   ^ ?

BTW: not giving _any_ optimization options is equivalent to -Onot, IIRC.


Cheers,
Michael
-- 
Lehrstuhl-BeleuchtungMichael Weber [EMAIL PROTECTED]
Lehrstuhl für Informatik II
RWTH Aachen
WWW: http://www-i2.informatik.rwth-aachen.de/Software/Haskell/



Problem with 4.05

2000-02-04 Thread Andy Davies

I've just tried to upgrade to the latest GHC binaries for NT (Cygwin) -
which appears to be ghc-4.05( no 4.06 yet?) The binaries install fine
and appear to compile simple Haskell programs (such as HelloWorld), but
when I try to run the resulting executable I get the message:
The procedure entry point PrelException_NonTermination_static_closure
could not be located in the dynamic link library HSprel.dll.

The dll is in the right place, but clearly something is up. Version 4.03
worked fine.

Help!!

Andy
--
Dr Andy Davies
School of Electronic and Electrical Engineering
University of Leeds
Leeds, LS2 9JT, UK
Tel: (0113) 233 2078Fax: (0113) 233 2032



Re: bug in ghc-4.06 ?

2000-02-04 Thread Jeffrey R. Lewis

Simon Peyton-Jones wrote:

 | If y'all agree that GHC should match hugs on this, it's only
 | about a 4 line
 | fix - I've tried it out already.  On the other hand, I don't
 | think that this
 | will make Sergey a happy camper.  Many instance declarations
 | need to be
 | tweaked.  It's a tedious job, but straightforward.

 I'd buy that, Jeff.  Unless anyone disagrees, why don't you go ahead
 and make the change?  It may require tweaking of not only instance
 decls but also ordinary decls with type signatures, right?  But only
 for people who use overlapping instance decls.

Yes, right on both counts.  And the compiler is kind enough to tell you
exactly what you need to add.



 When you make the fix, could you put the entire text of your message
 in as a comment?  (Edit it if you like, of course, but don't remove
 the examples.  I have slowly come to realise that whenever one makes
 a 2-line fix motivated by a strange case one should put the strange
 case in as a comment. I have often reversed such changes two years later
 because I though they were bogus, only to rediscover the strange case...)

Done.

--Jeff




Re: parse error in Hugs98 library

2000-02-04 Thread Malcolm Wallace

Sven writes:

  Does ghc have a problem with the 'primitive' declaration? [...]

 Exactly. In GHC (and probably already in NHC, too. Malcolm?) you
 have to write
foreign import unsafe getRandomSeed :: IO Int

Yes, since 1999-11-19, nhc98 also supports the new FFI.

Regards,
Malcolm




RE: CONTRIB/pphs

2000-02-04 Thread Simon Marlow

 No, there isn't any ./CVS/ directory entry in the current directory
 I am using. Maybe the problem is the absence of a fptools/CVS/ and/or
 fptools/CONTRIB/CVS directory in the FP Tools cvs server.
 
 When I checkout the complete fptools there is no problem.

I've seen this one before, but can't remember what caused it.

Anyway, try this (assuming you've got a checkout of GHC already):

$ cd fptools
$ cvs up -Pd CONTRIB

Cheers,
Simon



Quicker compilation for GHC users running x86-Linux

2000-02-04 Thread Julian Seward (Intl Vendor)


Folks,

The adventurous among you may like to try an innovation
which in some cases nearly doubles the speed at which 
ghc compiles programs.  This innovation is our native code
generator, which has long been in the GHC source tree,
but has only just been made to work for x86.  It reduces
compilation time by avoiding gcc (and perl) entirely,
and directly emitting x86 assembly code.

* Only x86 Linux is currently working.  I guess it
  should not be too much trouble to emit x86 code for
  Win32.  GHC also used to be able to emit Sparc and Alpha
  code, but these currently do not work.  Brave/foolhardy :-)
  souls may like to have a go resurrecting them; we will
  advise and supply debugging tips.  Or even writing new
  ports; IA64, anyone?

* This functionality is only available from the current
  CVS development branch.  It is NOT available in the
  standard 4.06 distribution, unfortunately.  In order
  to use it, build ghc from the CVS repository.  Then
  you only need to add -fasm-x86 to your command lines
  to use it.

* Stability: all of the nofib suite runs, and the compiler
  can compile itself via the native-code route.  This means
  it works well enough to be useful.  The generated code is
  5-10% slower than the standard route, but that's fine for
  debugging/development work.

  Regard this as beta-release functionality.  It works pretty
  well, but there are known issues which need to be resolved 
  before full-scale use (see ghc/compiler/nativeGen/NOTES).
  If stability/reliability are important to you, stick with
  the recently released 4.06 version.

* Please try it out!  I would be pleased to get feedback on it.

J



Re: More on randoms

2000-02-04 Thread Jerzy Karczmarczuk

Two things.

We have seen many times (last was Matt Harden) such definitions :

  class RandomGen g where
 next :: g - (Int, g)
 split :: g - (g, g)
 genRange :: g - (Int, Int)
 genRange _ = (minBound, maxBound)

Do you always use integer random numbers?

I don't know about you, but in my milieu 99% of random number
applications need *real*, floating RN, as fast as possible. If
the Haskell standard libraries offer only the basic integer RNG,
which will force all the users to reconstruct the needed reals,
this is not extremely painful, but anyway.
I would love having 'next' returning reals as well...
And vectors (with decently uncorrelated elements). Etc.

Do you think that all that must be manufactured by the user, or
can one parameterize the R. Gen. class a bit differently?

==

I haven't follow this discussion since the beginning, so I might
try to break an open door. The question is the following: would it
be a bad idea to provide a 'randomize' primitive, generating an
unexpected random value based on the internal clock or other
system properties? I haven't seen that here. It *is* useful.

Jerzy Karczmarczuk
Caen, France



Re: More on randoms

2000-02-04 Thread Marc van Dongen


Jerzy Karczmarczuk ([EMAIL PROTECTED]) wrote:

[...]

: the Haskell standard libraries offer only the basic integer RNG,
: which will force all the users to reconstruct the needed reals,
: this is not extremely painful, but anyway.
: I would love having 'next' returning reals as well...
: And vectors (with decently uncorrelated elements). Etc.

Yes please. But do change the word vector into [Integer].


[...]
 
Regards,


Marc van Dongen



Re: More on randoms

2000-02-04 Thread Tom Pledger

Jerzy Karczmarczuk writes:
  [...]
  I would love having 'next' returning reals as well...
  And vectors (with decently uncorrelated elements). Etc.
  
  Do you think that all that must be manufactured by the user, or
  can one parameterize the R. Gen. class a bit differently?

Try making each of those types an instance of Random, and using random
instead of next.  Someone (the user or the Haskell implementor) still
has to manufacture the instances, but only once.

  I haven't follow this discussion since the beginning, so I might
  try to break an open door. The question is the following: would it
  be a bad idea to provide a 'randomize' primitive, generating an
  unexpected random value based on the internal clock or other
  system properties? I haven't seen that here. It *is* useful.

newStdGen :: IO StdGen

should do the trick.  If you want a generator of a type other than
StdGen, you can always use a StdGen generator to seed it.

Regards,
Tom



Re: More on randoms

2000-02-04 Thread George Russell

Jerzy Karczmarczuk wrote:
   class RandomGen g where
  next :: g - (Int, g)
  split :: g - (g, g)
  genRange :: g - (Int, Int)
  genRange _ = (minBound, maxBound)
 
 Do you always use integer random numbers?
No.  But this is the primitive class we're discussing here.  The library
also defines
   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 
with
   instance Random Float
   instance Random Double

Where no range is specified the float or double should be in the range
[0,1).  It should of course be uniformly distributed.

It is reasonable IMHO that the primitive random generator should
generate integers rather than floats, as I think most pseudo-random
generation methods generate integers of some sort.



more on Random

2000-02-04 Thread S.D.Mechveliani

More on randoms.

Haskell uses the names `next', `split' for Random.
Maybe, it is better to add some prefix or suffix?
For there are so many basic operations in the universe that can be 
naturally called `next' and `split'. And Random does not look so 
priveleged to enjoy privately such a simple names.

Second.

Jerzy Karczmarczuk  [EMAIL PROTECTED],
Marc van Dongen [EMAIL PROTECTED]   wrote

K: the Haskell standard libraries offer only the basic integer RNG,
K: which will force all the users to reconstruct the needed reals,
K: this is not extremely painful, but anyway.
K: I would love having 'next' returning reals as well...
K: And vectors (with decently uncorrelated elements). Etc.

D Yes please. But do change the word vector into [Integer].


Maybe I am missing something, but why people need `next',
is not  randomR   enough?
Let for example, one needs a random vector. Define

  instance (Random a) = Random (Vector a)
where
   -- put a random vector "between vl and vh" to have random
   -- components "between" l(i) and h(i)  for each  i
   --
randomR (Vec lows, Vec highs) g = (Vec $ reverse xs, g')
   where
   (xs,g') = foldl rnd ([],g) $ zip lows highs

   rnd (xs,g) (l,h) = (x:xs,g')  where  (x,g') = randomR (l,h) g

What is wrong here?

As to Real, probably, there exists the standard  randomR  for it? 


--
Sergey Mechveliani
[EMAIL PROTECTED]






Re: more on Random

2000-02-04 Thread Koen Claessen

S.D.Mechveliani wrote:

 | Haskell uses the names `next', `split' for Random.
 | Maybe, it is better to add some prefix or suffix?

No!

Haskell has a perfectly fine module system which can take
care of these kind of issues. If you have other definitions
of "split" or "next", use "Random.split" or "Random.next".
(And there you have your prefix -- for free!)

Regards,
Koen.

--
Koen Claessen http://www.cs.chalmers.se/~koen 
phone:+46-31-772 5424  e-mail:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden




qualified names

2000-02-04 Thread S.D.Mechveliani

I wrote recently on the need of prefix or suffix for `next',`split'
of Random. 
Somebody corrected me, saying that  Random.next
is, at least, possible.
It is all right. But I would like to add something.

If  goodOp  is an operation of *class* C, then C.goodOp
- when needed, - looks like a good disambiguation forgoodOp
(is it of Haskell ?).
But if C is *module* in some program system, then  C.goodOp
may be useful, but not so good as for the class case.
Because the developer often needs to rename the modules, to move
items between modules ...
But again, this hardly touches the module names, that are the part
of the Standard, like Random. 

--
Sergey Mechveliani
[EMAIL PROTECTED]




Re: qualified names

2000-02-04 Thread Fergus Henderson

On 04-Feb-2000, S.D.Mechveliani [EMAIL PROTECTED] wrote:
 If  goodOp  is an operation of *class* C, then C.goodOp
 - when needed, - looks like a good disambiguation forgoodOp
 (is it of Haskell ?).

No, Haskell doesn't allow that.

Nor does Mercury allow the equivalent, though this feature
has been requested a couple of times on the Mercury mailing
lists.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.



Re: More on randoms

2000-02-04 Thread Matt Harden

Matt Harden wrote:
 
 ...  Darn.  Now I want the genRange operation again.  The
 "clarification" can really be a significant performance cost.  Not to
 mention, you're also shortening the period of the RNG (perhaps by a
 factor of 4!).
 
 Can we have both (see below)?
 
  class RandomGen g where
 next :: g - (Int, g)
 split :: g - (g, g)
 genRange :: g - (Int, Int)
 genRange _ = (minBound, maxBound)
 
 Put the "clarification" in, but then allow the implementer to optionally
 provide a different range?  If a genRange is provided, it should fit the
 requirements described earlier, of course.  And as someone suggested,
 (genRange _|_) should always be defined (not _|_).
 
 Regards,
 Matt Harden

Simon, do you think we could have the *optional* genRange described
above?  If that approach is chosen, then the changes to GHC and Hugs
are rather painless.  In fact, below I've attached a patch based on
Hugs98-Sept1999 (a context diff).  After this patch, my tests that
failed before now pass with flying colors.  I do need to put some
comments in though.  By the way, I think it's clear that much of the
code in Random.hs could be made more efficient.  I went for the
simplest possible change in this case, however.


*** Random.hs.orig  Fri Oct 15 21:50:13 1999
--- Random.hs   Fri Feb  4 22:57:39 2000
***
*** 28,33 
--- 28,35 
  class RandomGen g where
 next  :: g - (Int, g)
 split :: g - (g, g)
+genRange :: g - (Int, Int)
+genRange = const (minBound, maxBound)


  -- An efficient and portable combined random number generator: ---
***
*** 84,94 
--- 86,100 

  StdGen t1 t2 = snd (next std)

+ stdRange:: StdGen - (Int, Int)
+ stdRange = const (1, 2147483562)
+
  -- A standard instance of RandomGen: -

  instance RandomGen StdGen where
next  = stdNext
split = stdSplit
+   genRange = stdRange

  instance Show StdGen where
showsPrec p (StdGen s1 s2)
***
*** 167,182 
  randomIvalInteger :: (RandomGen g, Num a) = (Integer, Integer) - g - (a, g)
  randomIvalInteger (l,h) rng
   | l  h = randomIvalInteger (h,l) rng
!  | otherwise = case (f n 1 rng) of
!  (v, rng') - (fromInteger (l + v `mod` k), rng')
 where
   k = h - l + 1
!  b = 2147483561
   n = iLogBase b k

   f 0 acc g = (acc, g)
   f n acc g = let (x,g') = next g
!in f (n-1) (fromInt x + acc * b) g'

  randomIvalDouble :: (RandomGen g, Fractional a)
= (Double, Double) - (Double - a) - g - (a, g)
--- 173,190 
  randomIvalInteger :: (RandomGen g, Num a) = (Integer, Integer) - g - (a, g)
  randomIvalInteger (l,h) rng
   | l  h = randomIvalInteger (h,l) rng
!  | otherwise = case (f n 0 rng) of
!  (v, rng') | v  (b^n `mod` k) - randomIvalInteger (l,h) rng'
!| otherwise - (fromInteger (l + v `mod` k), rng')
 where
   k = h - l + 1
!  (c,d) = genRange rng
!  b = (toInteger d) - (toInteger c) + 1
   n = iLogBase b k

   f 0 acc g = (acc, g)
   f n acc g = let (x,g') = next g
!in f (n-1) ((fromInt x - fromInt c) + acc * b) g'

  randomIvalDouble :: (RandomGen g, Fractional a)
= (Double, Double) - (Double - a) - g - (a, g)
***
*** 197,203 
  intRange  = toInteger (maxBound::Int) - toInteger (minBound::Int)

  iLogBase :: Integer - Integer - Integer
! iLogBase b i = if i  b then 1 else 1 + iLogBase b (i `div` b)


  -- The global standard random number generator: --
--- 205,212 
  intRange  = toInteger (maxBound::Int) - toInteger (minBound::Int)

  iLogBase :: Integer - Integer - Integer
! iLogBase b 1 = 0
! iLogBase b i | i1 = 1 + iLogBase b ((i-1) `div` b + 1)


  -- The global standard random number generator: --