Re: [Haskell-cafe] Installing and running QuickCheck

2005-04-13 Thread adam
Hi Daniel,

Yes, importing Data.Char worked, but revealed other problems.  Now I get the
following.

ERROR C:\Program Files\Hugs98\libraries\QuickCheck.hs:161 - Undefined variable
 fromInt
Monad

This, however, I have seen before, and it has to do with different versions of
Prelude, where fromInt was removed and fromInteger put in.  From hugs-bugs, we
find that we need to just change fromInt to fromInteger on the appropriate
line.

http://www.haskell.org/pipermail/hugs-bugs/2005-January/001537.html


So, starting with line 160 of QuickCheck.hs should read:

instance Arbitrary Integer where
  arbitrary = sized $ \n - choose (-fromIntegral n,fromIntegral n)
  coarbitrary n = variant (fromInteger (if n = 0 then 2*n else 2*(-n) + 1))

And with these two changes, QuickCheck compiles.  Now I have to see how it
works.

Thanks,
Adam

Quoting Daniel Fischer [EMAIL PROTECTED]:

 Hm,

 no instance Arbitrary Char is provided in the QuickCheck modules that came
 with my hugs or ghc. Probably the author just forgot to import Data.Char. Try
 inserting that in QuickCheck.hs.

 Hope that works,
 Daniel


This message was sent using IMP, the Internet Messaging Program.

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


Re: [Haskell-cafe] Installing and running QuickCheck

2005-04-12 Thread Daniel Fischer
Hm,

no instance Arbitrary Char is provided in the QuickCheck modules that came 
with my hugs or ghc. Probably the author just forgot to import Data.Char. Try 
inserting that in QuickCheck.hs.

Hope that works,
Daniel

Am Samstag, 9. April 2005 21:10 schrieb Adam Wyner:
 Hi,

 I'd like to use QuickCheck for testing Haskell programs.  I'm using Hugs
 in Windows.  I'm a newbie to Haskell.

 Just running QuickCheck.hs itself, which comes with the Hugs98
 libraries, I get an error message and the Monad command line, which
 indicates that quickcheck didn't load.

 ERROR C:\Program Files\Hugs98/libraries\QuickCheck.hs:147 - Undefined
 variable  chr
 Monad

 Here is the line in QuickCheck.hs which leads to the error.

 instance Arbitrary Char where
arbitrary = choose (32,255) = \n - return (chr n)
coarbitrary n = variant (ord n)

 This code is from the website:

 http://www.cs.chalmers.se/~rjmh/QuickCheck/QuickCheck.hs

 I tested it with the following module, as per the instructions in on
 QuickCheck's manual page:
 
 module TestQuickCheck

 where

 import QuickCheck

 prop_RevRev xs = reverse (reverse xs) == xs
where types = xs::[Int]
 
 Loading just this, I get the same error:

 Prelude :l TestQuickCheck
 ERROR C:\Program Files\Hugs98/libraries\QuickCheck.hs:147 - Undefined
 variable
   chr
 Monad

 I know others report using QuickCheck, so this problem must have been
 resolved.

 Also, I guess the quickcheck script is for Linux alone?  Any scripts for
 Hugs in Windows?

 Cheers,
 Adam

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


[Haskell-cafe] Installing and running QuickCheck

2005-04-11 Thread Adam Wyner
Hi,
I'd like to use QuickCheck for testing Haskell programs.  I'm using Hugs 
in Windows.  I'm a newbie to Haskell.

Just running QuickCheck.hs itself, which comes with the Hugs98 
libraries, I get an error message and the Monad command line, which 
indicates that quickcheck didn't load.

ERROR C:\Program Files\Hugs98/libraries\QuickCheck.hs:147 - Undefined 
variable  chr
Monad

Here is the line in QuickCheck.hs which leads to the error.
instance Arbitrary Char where
  arbitrary = choose (32,255) = \n - return (chr n)
  coarbitrary n = variant (ord n)
This code is from the website:
http://www.cs.chalmers.se/~rjmh/QuickCheck/QuickCheck.hs
I tested it with the following module, as per the instructions in on 
QuickCheck's manual page:

module TestQuickCheck

where
import QuickCheck
prop_RevRev xs = reverse (reverse xs) == xs
  where types = xs::[Int]

Loading just this, I get the same error:
Prelude :l TestQuickCheck
ERROR C:\Program Files\Hugs98/libraries\QuickCheck.hs:147 - Undefined 
variable
 chr
Monad

I know others report using QuickCheck, so this problem must have been 
resolved.

Also, I guess the quickcheck script is for Linux alone?  Any scripts for 
Hugs in Windows?

Cheers,
Adam
begin:vcard
fn:Adam Zachary Wyner
n:Wyner;Adam Zachary
org:King's College London;Department of Computer Science
adr:;;26-29 Drury Lane;London;;WC2B 5RL;United Kingdom
email;internet:[EMAIL PROTECTED]
tel;work:+44-207-848-2476
tel;fax:+44-207-848-2851
tel;cell:+44-079-8482-3438
url:http://www.dcs.kcl.ac.uk/pg/wyner
version:2.1
end:vcard

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