[Haskell-cafe] Stack & Test Coverage

Artem Pelenitsyn a.pelenitsyn at gmail.com
Thu Sep 5 06:39:08 UTC 2019


Hello Hilco,

Please, do file a bug.

--
Best, Artem

On Thu, Sep 5, 2019, 1:26 AM Hilco Wijbenga <hilco.wijbenga at gmail.com>
wrote:

> On Wed, Sep 4, 2019 at 10:14 PM Hilco Wijbenga <hilco.wijbenga at gmail.com>
> wrote:
> >
> > On Tue, Sep 3, 2019 at 11:14 PM Ben Gamari <ben at smart-cactus.org> wrote:
> > >
> > > On September 4, 2019 4:32:29 AM GMT+02:00, Hilco Wijbenga <
> hilco.wijbenga at gmail.com> wrote:
> > > >Hi all,
> > > >
> > > >I have a very simple
> > > >
> > > >newtype Index = Index Int deriving (Eq, Ord, Enum)
> > > >
> > > >for which I have written tests with both HSpec and QuickCheck.
> > > >Specifically, I have written tests for "==", "/=", "compare" (for all
> > > >of EQ, LT, and GT), and "toEnum" & "fromEnum". So I thought I had
> > > >_very_ thoroughly covered that one line. :-)
> > > >
> > > >Unfortunately, after running "stack clean ; stack test --coverage" I
> > > >see in the HTML report that only Eq has been tested and that Ord and
> > > >Enum have _no_ coverage (i.e. "never executed").
> > > >
> > > >(The module also has some regular functions and an explicit Show
> > > >instance [all with tests] and those are apparently fine. So coverage
> > > >does seem to work but not the way I expect?)
> > > >
> > > >What am I doing wrong?
> > > >
> > > >Cheers,
> > > >Hilco
> > > >_______________________________________________
> > > >Haskell-Cafe mailing list
> > > >To (un)subscribe, modify options or view archives go to:
> > > >http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> > > >Only members subscribed via the mailman list are allowed to post.
> > >
> > > This sounds like it may be a ghc bug. Can you open a ticket at
> https://gitlab.haskell.org/ghc/ghc?
> >
> > Well, I wasn't expecting that. :-)
> >
> > I created a tiny test project with just the newtype and even removed
> > Enum. I tried all LTSs listed at https://www.stackage.org from
> > LST-3.22 all the way up to nightly-2019-09-04 and they all behave the
> > same way. (Stack is _awesome_ for this.) I also tried "data" instead
> > of "newtype". That made no difference.
> >
> > Are you sure this might be a GHC bug? Surely someone would have
> > noticed sometime during the last 4 years? It would have been in GHC
> > 7.10.2 already. Anyway, if "yes" then I'll create an issue. It should
> > be very easy to reproduce. (I don't mean to doubt you but it's rather
> > rare in software that it's "the compiler" and not "the developer". :-)
> > I don't want to waste anyone's time.)
>
> Mmm, so for sake of completeness:
>
> ----- Lib.hs
> module Lib where
> newtype Index = Index Int deriving (Eq, Ord, Show)
>
> ----- LibSpec.hs
> module LibSpec (spec) where
>
> import Test.Hspec
> import Test.QuickCheck
> import Lib
>
> genValidIndexes :: Gen (Index, Index)
> genValidIndexes = do lft <- choose (0, 100)
>     rgt <- choose (0, 100)
>     pure (Index lft, Index rgt)
>
> prop_EqIndex :: (Index, Index) -> Bool
> prop_EqIndex (lftIndex@(Index lft), rgtIndex@(Index rgt)) = (lftIndex
> == rgtIndex) == (lft == rgt)
>
> prop_OrdIndex :: (Index, Index) -> Bool
> prop_OrdIndex (lftIndex@(Index lft), rgtIndex@(Index rgt)) = compare
> lftIndex rgtIndex == compare lft rgt
>
> spec :: Spec
> spec
>   = do
>      describe "Index::Eq" $
>        do it "Index 0 == Index 0" $ Index 0 == Index 0 `shouldBe` True
>           it "Index 0 /= Index 1" $ Index 0 /= Index 1 `shouldBe` True
>           it "Index 1 /= Index 0" $ Index 1 /= Index 0 `shouldBe` True
>           it "prop_Eq" $ property $ forAll genValidIndexes prop_EqIndex
>      describe "Index::Ord" $
>        do it "compare (Index 0) (Index 0)" $ compare (Index 0) (Index
> 0) `shouldBe` EQ
>           it "compare (Index 1) (Index 2)" $ compare (Index 1) (Index
> 2) `shouldBe` LT
>           it "compare (Index 2) (Index 1)" $ compare (Index 2) (Index
> 1) `shouldBe` GT
>           it "prop_OrdIndex" $ property $ forAll genValidIndexes
> prop_OrdIndex
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20190905/04d025a8/attachment.html>


More information about the Haskell-Cafe mailing list