From 61e6a363778f956a4470baf470b675d70bb3554b Mon Sep 17 00:00:00 2001 From: Preetham Gujjula Date: Mon, 20 May 2024 19:49:06 -0400 Subject: [PATCH] Resolve Haddock out-of-scope identifier warnings Fix all broken Haddock links. Now Haddock doesn't emit any warnings about out-of-scope identifiers. Warnings about unknown link destinations are more complicated to resolve and are not handled in this commit. --- src/Test/QuickCheck.hs | 12 +++++------ src/Test/QuickCheck/Arbitrary.hs | 3 ++- src/Test/QuickCheck/Gen.hs | 4 ++-- src/Test/QuickCheck/Modifiers.hs | 12 +++++------ src/Test/QuickCheck/Property.hs | 17 ++++++++------- src/Test/QuickCheck/State.hs | 37 ++++++++++++++++---------------- src/Test/QuickCheck/Test.hs | 16 +++++++------- 7 files changed, 52 insertions(+), 49 deletions(-) diff --git a/src/Test/QuickCheck.hs b/src/Test/QuickCheck.hs index 78cbaa1e..b111768e 100644 --- a/src/Test/QuickCheck.hs +++ b/src/Test/QuickCheck.hs @@ -50,8 +50,8 @@ them to: +++ Ok, passed 100 tests. @ -That's because GHCi will default any type variables in your property to '()', so in the example -above @quickCheck@ was really testing that '()' is equal to itself. To avoid this behaviour it +That's because GHCi will default any type variables in your property to @()@, so in the example +above @quickCheck@ was really testing that @()@ is equal to itself. To avoid this behaviour it is best practise to monomorphise your polymorphic properties when testing: @ @@ -236,24 +236,24 @@ module Test.QuickCheck -- -- @ -- -- Functions cannot be shown (but see 'Function') - -- prop_TakeDropWhile ('Blind' p) (xs :: ['A']) = + -- prop_TakeDropWhile ('Blind' p) (xs :: ['Test.QuickCheck.Poly.A']) = -- takeWhile p xs ++ dropWhile p xs == xs -- @ -- -- @ - -- prop_TakeDrop ('NonNegative' n) (xs :: ['A']) = + -- prop_TakeDrop ('NonNegative' n) (xs :: ['Test.QuickCheck.Poly.A']) = -- take n xs ++ drop n xs == xs -- @ -- -- @ -- -- cycle does not work for empty lists - -- prop_Cycle ('NonNegative' n) ('NonEmpty' (xs :: ['A'])) = + -- prop_Cycle ('NonNegative' n) ('NonEmpty' (xs :: ['Test.QuickCheck.Poly.A'])) = -- take n (cycle xs) == take n (xs ++ cycle xs) -- @ -- -- @ -- -- Instead of 'forAll' 'orderedList' - -- prop_Sort ('Ordered' (xs :: ['OrdA'])) = + -- prop_Sort ('Ordered' (xs :: ['Test.QuickCheck.Poly.OrdA'])) = -- sort xs == xs -- @ , Blind(..) diff --git a/src/Test/QuickCheck/Arbitrary.hs b/src/Test/QuickCheck/Arbitrary.hs index 8d80ea43..1febc6fd 100644 --- a/src/Test/QuickCheck/Arbitrary.hs +++ b/src/Test/QuickCheck/Arbitrary.hs @@ -202,7 +202,8 @@ class Arbitrary a where -- It is worth spending time thinking about what sort of test data -- you want - good generators are often the difference between -- finding bugs and not finding them. You can use 'sample', - -- 'label' and 'classify' to check the quality of your test data. + -- 'Test.QuickCheck.label' and 'Test.QuickCheck.classify' to check the quality + -- of your test data. -- -- There is no generic @arbitrary@ implementation included because we don't -- know how to make a high-quality one. If you want one, consider using the diff --git a/src/Test/QuickCheck/Gen.hs b/src/Test/QuickCheck/Gen.hs index 27ac9b56..7bd1ff4f 100644 --- a/src/Test/QuickCheck/Gen.hs +++ b/src/Test/QuickCheck/Gen.hs @@ -157,7 +157,7 @@ scale f g = sized (\n -> resize (f n) g) choose :: Random a => (a,a) -> Gen a choose rng = MkGen (\r _ -> let (x,_) = randomR rng r in x) --- | Generates a random element over the natural range of `a`. +-- | Generates a random element over the natural range of @a@. chooseAny :: Random a => Gen a chooseAny = MkGen (\r _ -> let (x,_) = random r in x) @@ -244,7 +244,7 @@ sample' :: Gen a -> IO [a] sample' g = generate (sequence [ resize n g | n <- [0,2..20] ]) --- | Generates some example values and prints them to 'stdout'. +-- | Generates some example values and prints them to 'System.IO.stdout'. sample :: Show a => Gen a -> IO () sample g = sequence_ [ do r <- newQCGen diff --git a/src/Test/QuickCheck/Modifiers.hs b/src/Test/QuickCheck/Modifiers.hs index 28c10ddc..c177e64f 100644 --- a/src/Test/QuickCheck/Modifiers.hs +++ b/src/Test/QuickCheck/Modifiers.hs @@ -24,24 +24,24 @@ -- -- @ -- -- Functions cannot be shown (but see "Test.QuickCheck.Function") --- prop_TakeDropWhile ('Blind' p) (xs :: ['A']) = +-- prop_TakeDropWhile ('Blind' p) (xs :: ['Test.QuickCheck.Poly.A']) = -- takeWhile p xs ++ dropWhile p xs == xs -- @ -- -- @ --- prop_TakeDrop ('NonNegative' n) (xs :: ['A']) = +-- prop_TakeDrop ('NonNegative' n) (xs :: ['Test.QuickCheck.Poly.A']) = -- take n xs ++ drop n xs == xs -- @ -- -- @ -- -- cycle does not work for empty lists --- prop_Cycle ('NonNegative' n) ('NonEmpty' (xs :: ['A'])) = +-- prop_Cycle ('NonNegative' n) ('NonEmpty' (xs :: ['Test.QuickCheck.Poly.A'])) = -- take n (cycle xs) == take n (xs ++ cycle xs) -- @ -- -- @ --- -- Instead of 'forAll' 'orderedList' --- prop_Sort ('Ordered' (xs :: ['OrdA'])) = +-- -- Instead of 'Test.QuickCheck.forAll' 'orderedList' +-- prop_Sort ('Ordered' (xs :: ['Test.QuickCheck.Poly.OrdA'])) = -- sort xs == xs -- @ module Test.QuickCheck.Modifiers @@ -182,7 +182,7 @@ instance Arbitrary a => Arbitrary (NonEmptyList a) where -- -- > prop_take_10 :: InfiniteList Char -> Bool -- > prop_take_10 (InfiniteList xs _) = --- > or [ x == 'a' | x <- take 10 xs ] +-- > or [ x == \'a\' | x <- take 10 xs ] -- -- In the following counterexample, the list must start with @"bbbbbbbbbb"@ but -- the remaining (infinite) part can contain anything: diff --git a/src/Test/QuickCheck/Property.hs b/src/Test/QuickCheck/Property.hs index 94c98912..7736593c 100644 --- a/src/Test/QuickCheck/Property.hs +++ b/src/Test/QuickCheck/Property.hs @@ -525,8 +525,9 @@ withMaxSize :: Testable prop => Int -> prop -> Property withMaxSize n = n `seq` mapTotalResult (\res -> res{ maybeMaxTestSize = Just n }) #ifndef NO_TYPEABLE --- | Return a value in the 'witnesses' field of the 'Result' returned by 'quickCheckResult'. Witnesses --- are returned outer-most first. +-- | Return a value in the 'Test.QuickCheck.witnesses' field of the 'Result' +-- returned by 'Test.QuickCheck.quickCheckResult'. Witnesses are returned +-- outer-most first. -- -- In ghci, for example: -- @@ -765,7 +766,7 @@ tabulate key values = mapTotalResult $ \res -> res { tables = [(key, value) | value <- values] ++ tables res } --- | Checks that the values in a given 'table' appear a certain proportion of +-- | Checks that the values in a given @table@ appear a certain proportion of -- the time. A call to 'coverTable' @table@ @[(x1, p1), ..., (xn, pn)]@ asserts -- that of the values in @table@, @x1@ should appear at least @p1@ percent of -- the time that @table@ appears, @x2@ at least @p2@ percent of the time that @@ -774,7 +775,7 @@ tabulate key values = -- __Note:__ If the coverage check fails, QuickCheck prints out a warning, but -- the property does /not/ fail. To make the property fail, use 'checkCoverage'. -- --- Continuing the example from the 'tabular' combinator... +-- Continuing the example from the 'tabulate' combinator... -- -- > data Command = LogIn | LogOut | SendMessage String deriving (Data, Show) -- > prop_chatroom :: [Command] -> Property @@ -908,8 +909,8 @@ forAllShrinkBlind gen shrinker pf = unProperty $ shrinking shrinker x pf --- | Nondeterministic choice: 'p1' '.&.' 'p2' picks randomly one of --- 'p1' and 'p2' to test. If you test the property 100 times it +-- | Nondeterministic choice: @p1@ '.&.' @p2@ picks randomly one of +-- @p1@ and @p2@ to test. If you test the property 100 times it -- makes 100 random choices. (.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property p1 .&. p2 = @@ -919,7 +920,7 @@ p1 .&. p2 = counterexample (if b then "LHS" else "RHS") $ if b then property p1 else property p2 --- | Conjunction: 'p1' '.&&.' 'p2' passes if both 'p1' and 'p2' pass. +-- | Conjunction: @p1@ '.&&.' @p2@ passes if both @p1@ and @p2@ pass. (.&&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property p1 .&&. p2 = conjoin [property p1, property p2] @@ -957,7 +958,7 @@ conjoin ps = classes = classes result ++ classes r, tables = tables result ++ tables r } --- | Disjunction: 'p1' '.||.' 'p2' passes unless 'p1' and 'p2' simultaneously fail. +-- | Disjunction: @p1@ '.||.' @p2@ passes unless @p1@ and @p2@ simultaneously fail. (.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property p1 .||. p2 = disjoin [property p1, property p2] diff --git a/src/Test/QuickCheck/State.hs b/src/Test/QuickCheck/State.hs index 394d2b57..1470dc9a 100644 --- a/src/Test/QuickCheck/State.hs +++ b/src/Test/QuickCheck/State.hs @@ -63,33 +63,34 @@ data State -- ^ total number of failed shrinking steps } --- | The statistical parameters used by 'checkCoverage'. +-- | The statistical parameters used by 'Test.QuickCheck.checkCoverage'. data Confidence = Confidence { certainty :: Integer, - -- ^ How certain 'checkCoverage' must be before the property fails. - -- If the coverage requirement is met, and the certainty parameter is @n@, - -- then you should get a false positive at most one in @n@ runs of QuickCheck. - -- The default value is @10^9@. + -- ^ How certain 'Test.QuickCheck.checkCoverage' must be before the property + -- fails. If the coverage requirement is met, and the certainty parameter is + -- @n@, then you should get a false positive at most one in @n@ runs of + -- QuickCheck. The default value is @10^9@. -- - -- Lower values will speed up 'checkCoverage' at the cost of false - -- positives. + -- Lower values will speed up 'Test.QuickCheck.checkCoverage' at the cost of + -- false positives. -- - -- If you are using 'checkCoverage' as part of a test suite, you should - -- be careful not to set @certainty@ too low. If you want, say, a 1% chance - -- of a false positive during a project's lifetime, then @certainty@ should - -- be set to at least @100 * m * n@, where @m@ is the number of uses of - -- 'cover' in the test suite, and @n@ is the number of times you expect the - -- test suite to be run during the project's lifetime. The default value - -- is chosen to be big enough for most projects. + -- If you are using 'Test.QuickCheck.checkCoverage' as part of a test suite, + -- you should be careful not to set @certainty@ too low. If you want, say, a + -- 1% chance of a false positive during a project's lifetime, then + -- certainty@ should be set to at least @100 * m * n@, where @m@ is the + -- number of uses of 'Test.QuickCheck.cover' in the test suite, and @n@ is + -- the number of times you expect the test suite to be run during the + -- project's lifetime. The default value is chosen to be big enough for most + -- projects. tolerance :: Double - -- ^ For statistical reasons, 'checkCoverage' will not reject coverage - -- levels that are only slightly below the required levels. + -- ^ For statistical reasons, 'Test.QuickCheck.checkCoverage' will not + -- reject coverage levels that are only slightly below the required levels. -- If the required level is @p@ then an actual level of @tolerance * p@ -- will be accepted. The default value is @0.9@. -- - -- Lower values will speed up 'checkCoverage' at the cost of not detecting - -- minor coverage violations. + -- Lower values will speed up 'Test.QuickCheck.checkCoverage' at the cost of + -- not detecting minor coverage violations. } deriving Show diff --git a/src/Test/QuickCheck/Test.hs b/src/Test/QuickCheck/Test.hs index 8f913b49..ab6acaea 100644 --- a/src/Test/QuickCheck/Test.hs +++ b/src/Test/QuickCheck/Test.hs @@ -177,7 +177,7 @@ stdArgs = Args , maxShrinks = maxBound } --- | Tests a property and prints the results to 'stdout'. +-- | Tests a property and prints the results to 'System.IO.stdout'. -- -- By default up to 100 tests are performed, which may not be enough -- to find all bugs. To run more tests, use 'withMaxSuccess'. @@ -190,15 +190,15 @@ stdArgs = Args quickCheck :: Testable prop => prop -> IO () quickCheck p = quickCheckWith stdArgs p --- | Tests a property, using test arguments, and prints the results to 'stdout'. +-- | Tests a property, using test arguments, and prints the results to 'System.IO.stdout'. quickCheckWith :: Testable prop => Args -> prop -> IO () quickCheckWith args p = quickCheckWithResult args p >> return () --- | Tests a property, produces a test result, and prints the results to 'stdout'. +-- | Tests a property, produces a test result, and prints the results to 'System.IO.stdout'. quickCheckResult :: Testable prop => prop -> IO Result quickCheckResult p = quickCheckWithResult stdArgs p --- | Tests a property, using test arguments, produces a test result, and prints the results to 'stdout'. +-- | Tests a property, using test arguments, produces a test result, and prints the results to 'System.IO.stdout'. quickCheckWithResult :: Testable prop => Args -> prop -> IO Result quickCheckWithResult a p = withState a (\s -> test s (property p)) @@ -258,7 +258,7 @@ computeSize MkState{maxSuccessTests = ms, maxTestSize = mts, maxDiscardedRatio = clamp :: Ord a => a -> (a, a) -> a clamp x (l, h) = max l (min x h) --- | Tests a property and prints the results and all test cases generated to 'stdout'. +-- | Tests a property and prints the results and all test cases generated to 'System.IO.stdout'. -- This is just a convenience function that means the same as @'quickCheck' . 'verbose'@. -- -- Note: for technical reasons, the test case is printed out /after/ @@ -267,7 +267,7 @@ clamp x (l, h) = max l (min x h) verboseCheck :: Testable prop => prop -> IO () verboseCheck p = quickCheck (verbose p) --- | Tests a property, using test arguments, and prints the results and all test cases generated to 'stdout'. +-- | Tests a property, using test arguments, and prints the results and all test cases generated to 'System.IO.stdout'. -- This is just a convenience function that combines 'quickCheckWith' and 'verbose'. -- -- Note: for technical reasons, the test case is printed out /after/ @@ -276,7 +276,7 @@ verboseCheck p = quickCheck (verbose p) verboseCheckWith :: Testable prop => Args -> prop -> IO () verboseCheckWith args p = quickCheckWith args (verbose p) --- | Tests a property, produces a test result, and prints the results and all test cases generated to 'stdout'. +-- | Tests a property, produces a test result, and prints the results and all test cases generated to 'System.IO.stdout'. -- This is just a convenience function that combines 'quickCheckResult' and 'verbose'. -- -- Note: for technical reasons, the test case is printed out /after/ @@ -285,7 +285,7 @@ verboseCheckWith args p = quickCheckWith args (verbose p) verboseCheckResult :: Testable prop => prop -> IO Result verboseCheckResult p = quickCheckResult (verbose p) --- | Tests a property, using test arguments, produces a test result, and prints the results and all test cases generated to 'stdout'. +-- | Tests a property, using test arguments, produces a test result, and prints the results and all test cases generated to 'System.IO.stdout'. -- This is just a convenience function that combines 'quickCheckWithResult' and 'verbose'. -- -- Note: for technical reasons, the test case is printed out /after/