[Haskell-cafe] Installing and running QuickCheck

Adam Wyner adam at wyner.info
Sat Apr 9 15:10:22 EDT 2005


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
-------------- next part --------------
A non-text attachment was scrubbed...
Name: adam.vcf
Type: text/x-vcard
Size: 337 bytes
Desc: not available
Url : http://www.haskell.org//pipermail/haskell-cafe/attachments/20050409/d782982f/adam-0001.vcf


More information about the Haskell-Cafe mailing list