Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

HTF does not test props generated by TH

I want to do a number of similar tests on various types in my library.

To simplify things, assume I have a number of vector types implementing Num class, and I want to generate the same QuickCheck property check prop_absNorm x y = abs x + abs y >= abs (x+y) that would work on all of the types in library.

I generate such properties using TH:

$(writeTests
    (\t ->
        [d| prop_absNorm :: $(t) -> $(t) -> Bool
            prop_absNorm x y = abs x + abs y >= abs (x+y)
        |])
 )

My function to generate tests has the following signature:

writeTests :: (TypeQ -> Q [Dec]) -> Q [Dec]

This function looks for all instances of my vector class VectorMath (n::Nat) t (and, at the same time, instances of Num) through reify ''VectorMath and generates all prop functions accordingly. -ddump-splices shows something like this:

prop_absNormIntX4 :: Vector 4 Int -> Vector 4 Int -> Bool
prop_absNormIntX4 x y = abs x + abs y >= abs (x+y)
prop_absNormCIntX4 :: Vector 4 CInt -> Vector 4 CInt -> Bool
prop_absNormCIntX4 x y = abs x + abs y >= abs (x+y)
...
prop_absNormFloatX4 :: Vector 4 Float -> Vector 4 Float -> Bool
prop_absNormFloatX4 x y = abs x + abs y >= abs (x+y)
prop_absNormFloatX3 :: Vector 3 Float -> Vector 3 Float -> Bool
prop_absNormFloatX3 x y = abs x + abs y >= abs (x+y)

The problem is that all manually written properties are checked, but generated ones are not.

Note 1: I have generated and non-generated properties in the same file (i.e. TH expression $(..) is in the same file as the other props).

Note 2: the list of types for creation of prop functions is variable - I want to add other instances of VectorMath later, so they are automatically added into the test list.

I believe that the problem is that HTF (which presumably uses TH too) parses the original file, not the one with generated code - but I cannot get why this happens.

So my question is: how to solve this problem? If it is not possible to use TH-generated props, then is that possible to do QuickCheck tests on various types (i.e. that it substitutes them into prop_absNorm :: Vector 4 a -> Vector 4 a -> Bool)?

Also another alternative may be to use TH further to add test entries manually to htf_Main, but I have not figured out how to do this yet; and it does not look like a nice clean solution.

like image 973
artem Avatar asked Sep 25 '15 14:09

artem


3 Answers

If you know in advance what the names of the generated property tests are, then you could always manually define stubs so that HTF sees them, e.g.:

$(generate prop test for Int)
$(generate prop test for CInt)

prop_p1 = prop_absNormInt
prop_p2 = prop_absNormCInt

HTF will see the tests as prop_p1 and prop_p2. You shouldn't have to put type signatures on these stubs.

Another idea is to create your own source pre-processor to add these stubs for you (and give them better names). Your source pre-processor would automatically call htfpp to complete the pre-processing.

If you show me how your TH is invoked I can show you how to write the pre-processor.

Update:

Given your comment I would look at doing the following:

  1. Write a program to generate the test module source.
  2. Include that program and the output it generates in your cabal project.
  3. Tell users to run the program if they want to update the test module.

So - the test cases remain fixed until the program is run to regenerate the test module.

Having a static test module has the advantage that you can tell exactly what is being tested.

Having a program to recreate the test module gives you the ability to easily update it when new Num instances become available.

like image 112
ErikR Avatar answered Nov 15 '22 08:11

ErikR


Ok, I managed to solve this problem. The idea is to use TH to aggregate the tests and insert them into htfMain. On top of what I have in the question, this includes following steps:

  1. Convert all testable properties into IO actions running QuickCheck tests;
  2. Aggregate all tests into TestSuite;
  3. Aggregate all test suites into one list and put it into htfMain.

In order to use step 1 I had to use semi-internal function of HTF called qcAssertion :: (QCAssertion t) => t -> Assertion. This function is available, but not recommended for external use; it allows running QuickCheck tests nicely, integrating them into report.

To proceed with step 2, I use two functions from HTF: makeTestSuite and makeQuickCheckTest. I also use location function from TH to provide filename and line of the place where the splice with test template is inserted (for nicer test logs).

Step 3 is a tricky one: for this we need to find all generated test suites. The problem is that TH does not allow to browse through all functions (including generated) in a module. To overcome this, I added following type class:

class MultitypeTestSuite name where
    multitypeTestSuite :: name -> TestSuite

So my function writeTests generates a new data type data MTS[prop_name] and an instance of MultitypeTestSuite for that data type. This allows me later to use another splice function in htfMain that will generate a list of test suites out of instances of that class using reify:

aggregateTests :: ExpQ
aggregateTests = do
    ClassI _ instances <- reify ''MultitypeTestSuite
    liftM ListE . forM instances
          $ \... -> [e| multitypeTestSuite $(...) |]

In the end, including all generated tests together with manually written ones looks pretty simple:

main :: IO ()
main = htfMain $ htf_importedTests ++ $(aggregateTests)

So, by adjusting function $(writeTests) I am able now to generate and test properties that vary in argument type - for all types available in scope at the same type. Test results and logs are included the same way as original tests.

On that the problem is fully solved.

like image 45
artem Avatar answered Nov 15 '22 08:11

artem


HTF does not use TemplateHaskell for collecting the tests , this would slow down compilation-time significantly. Instead, HTF uses a custom preprocessor called htfpp. htfpp runs before the compiler (and thus before TemplateHaskell splices are expanded). This means that you cannot use automatic test discovery with htfpp when generating your tests with TemplateHaskell.

My suggestion: when you are using TemplateHaskell anyway, then just use TemplateHaskell to collect your generated test cases. This functionality is not built into HTF, but it's not difficult to implement such a function. Here is it:

-- file TH.hs
{-# LANGUAGE TemplateHaskell #-}
module TH ( genTestSuiteFromQcProps ) where

import Language.Haskell.TH

import Test.Framework
import Test.Framework.Location

genTestSuiteFromQcProps :: String -> [Name] -> Q Exp
genTestSuiteFromQcProps suiteName names =
    [| makeTestSuite $(stringE suiteName) $(listE genTests) |]
    where
      genTests :: [ExpQ]
      genTests =
          map genTest names
      genTest :: Name -> Q Exp
      genTest name =
          [| makeQuickCheckTest $(stringE (show name)) unknownLocation
                 (qcAssertion $(varE name)) |]

The function genTestSuiteFromQcProps takes the name of the test suite to generated and a list of names, referring to your QC properties. genTestSuiteFromQcProps returns an expression of type TestSuite. TestSuite is one of the types HTF uses to organize tests. (The htfpp preprocessor als uses the TestSuite type in its output.)

Here is how you wold use genTestSuiteFromQcProps:

-- file Main.hs
{-# OPTIONS_GHC -F -pgmF htfpp #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where

import TH
import Test.Framework

import {-@ HTF_TESTS @-} OtherTests

prop_additionCommutative :: Int -> Int -> Bool
prop_additionCommutative x y = (x + y) == (y + x)

prop_reverseReverseIdentity :: [Int] -> Bool
prop_reverseReverseIdentity l = l == reverse (reverse l)

myTestSuite :: TestSuite
myTestSuite =
    $(genTestSuiteFromQcProps
         "MyTestSuite"
         ['prop_additionCommutative
         ,'prop_reverseReverseIdentity])

main :: IO ()
main = htfMain (myTestSuite : htf_importedTests)

For your case, you would pass genTestSuiteFromQcProps the names of the QC properties you generated with TemplateHaskell.

The example also shows that you can mix test cases generated with the TemplateHaskell function with tests cases collected by htfpp. For completeness, here is the content of OtherTests:

{-# OPTIONS_GHC -F -pgmF htfpp #-}
module OtherTests ( htf_thisModulesTests) where

import Test.Framework

test_someOtherTest :: IO ()
test_someOtherTest =
    assertEqual 1 1
like image 24
stefanwehr Avatar answered Nov 15 '22 09:11

stefanwehr