
I spent whole day looking for a bug that lurks somewhere in my code, but I know I could find it in 2-3 hours if I only could write unit tests for my code. So the question is: how can I write HUnit and QuickCheck (and maybe SmallCheck) tests for GHC and possibly make them a part of testsuite? Janek

On Tue, Jul 30, 2013 at 05:28:12PM +0200, Jan Stolarek wrote:
I spent whole day looking for a bug that lurks somewhere in my code, but I know I could find it in 2-3 hours if I only could write unit tests for my code. So the question is: how can I write HUnit and QuickCheck (and maybe SmallCheck) tests for GHC and possibly make them a part of testsuite?
It's better not to use HUnit/QuickCheck/SmallCheck, as then you can add them to the testsuite and they can be run by everyone, without needing the libraries to be installed. Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

Thanks Ian. I think the matter of using HUnit or QuickCheck is not the most relevant here. The real question his how to test a single function from GHC sources (assuming that it is exported by module in which it is defined)? So let's say there is a module in GHC I want to test:
module Foo where
foo x y = x + y
And I want to write tests for it in the testsuite:
module FooTests where
import Foo
main = ASSERT (foo 2 2 == 4)
ASSERT (foo 0 1 == 1)
and so on (Hunit would only be a convenient interface here). The question is how can I import a GHC module from within the testsuite and call its functions to test it they behave propertly? An attempt to simply import the module results in compilation error:
Failed to load interface for ‛Foo’
It is a member of the hidden package ‛ghc-7.7.20130731’.
Use -v to see a list of the files searched for.
Is there a workaround for this?
Janek
----- Oryginalna wiadomość -----
Od: "Ian Lynagh"
I spent whole day looking for a bug that lurks somewhere in my code, but I know I could find it in 2-3 hours if I only could write unit tests for my code. So the question is: how can I write HUnit and QuickCheck (and maybe SmallCheck) tests for GHC and possibly make them a part of testsuite?
It's better not to use HUnit/QuickCheck/SmallCheck, as then you can add them to the testsuite and they can be run by everyone, without needing the libraries to be installed. Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

On Wed, Jul 31, 2013 at 04:10:46PM +0200, Jan Stolarek wrote:
and so on (Hunit would only be a convenient interface here). The question is how can I import a GHC module from within the testsuite and call its functions to test it they behave propertly? An attempt to simply import the module results in compilation error:
Failed to load interface for ‛Foo’ It is a member of the hidden package ‛ghc-7.7.20130731’. Use -v to see a list of the files searched for.
Is there a workaround for this?
You need to use "-package ghc" if you want to use the GHC API. Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

Thank you Ian - this indeed does the trick. But going a bit further I've encountered another problem. I need to run my computations in the Ghc session, because otherwise some actions fail with panic:
CmmCopyPropagationTest: CmmCopyPropagationTest: panic! (the 'impossible' happened)
(GHC version 7.7.20130731 for i386-unknown-linux):
v_unsafeGlobalDynFlags: not initialised
My understanding is that I can use runGhc function from Ghc module to run actions in Ghc monad and lift the result to IO monad. I'm having problems with the second paramter to runGhc function. Is there a robust way of obtaining that parameter so that the test is portable across machines (I want to make that test a part of the testsuite)?
Janek
----- Oryginalna wiadomość -----
Od: "Ian Lynagh"
and so on (Hunit would only be a convenient interface here). The question is how can I import a GHC module from within the testsuite and call its functions to test it they behave propertly? An attempt to simply import the module results in compilation error:
Failed to load interface for ‛Foo’ It is a member of the hidden package ‛ghc-7.7.20130731’. Use -v to see a list of the files searched for.
Is there a workaround for this?
You need to use "-package ghc" if you want to use the GHC API. Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

If you can make tests for some particular part of GHC, go right ahead. I don't really know how to test the whole of GHC using Quickcheck Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of Jan Stolarek | Sent: 30 July 2013 16:28 | To: ghc-devs | Subject: Unit-testing of GHC code | | I spent whole day looking for a bug that lurks somewhere in my code, but I know I | could find it in 2-3 hours if I only could write unit tests for my code. So the | question is: how can I write HUnit and QuickCheck (and maybe SmallCheck) tests | for GHC and possibly make them a part of testsuite? | | Janek | | _______________________________________________ | ghc-devs mailing list | ghc-devs@haskell.org | http://www.haskell.org/mailman/listinfo/ghc-devs
participants (3)
-
Ian Lynagh
-
Jan Stolarek
-
Simon Peyton-Jones