Unit-testing of GHC code

Jan Stolarek jan.stolarek at p.lodz.pl
Wed Jul 31 16:10:46 CEST 2013


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" <ian at well-typed.com>
Do: "Jan Stolarek" <jan.stolarek at p.lodz.pl>
DW: "ghc-devs" <ghc-devs at haskell.org>
Wysłane: środa, 31 lipiec 2013 13:31:44
Temat: Re: Unit-testing of GHC code

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/





More information about the ghc-devs mailing list