Skip to content

Commit

Permalink
TST Switch to tasty for testing
Browse files Browse the repository at this point in the history
Unlike test-framework, tasty is being actively maintained and seems to
work after just switching all the import statements
  • Loading branch information
luispedro committed May 4, 2021
1 parent 9732282 commit 19a7fbd
Show file tree
Hide file tree
Showing 17 changed files with 47 additions and 50 deletions.
1 change: 1 addition & 0 deletions ChangeLog
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
Unreleased
* write() returns the filename used
* Switch to tasty test framework

Version 1.3.0 2021-01-28 by luispedro
* Validate count() headers on --validate-only
Expand Down
7 changes: 3 additions & 4 deletions Tests-Src/Tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,10 +9,9 @@

module Main where

import Test.Framework
import Test.Framework.TH
import Test.HUnit
import Test.Framework.Providers.HUnit
import Test.Tasty
import Test.Tasty.TH
import Test.Tasty.HUnit
import Text.Parsec (parse)
import Text.Parsec.Combinator (eof)

Expand Down
5 changes: 2 additions & 3 deletions Tests-Src/Tests/Count.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,8 @@ module Tests.Count
( tgroup_Count
) where

import Test.Framework.TH
import Test.HUnit
import Test.Framework.Providers.HUnit
import Test.Tasty.TH
import Test.Tasty.HUnit

import qualified Data.IntervalIntMap as IM
import qualified Data.Set as S
Expand Down
7 changes: 3 additions & 4 deletions Tests-Src/Tests/FastQ.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,12 +6,11 @@ module Tests.FastQ
( tgroup_FastQ
) where

import Test.Framework.TH
import Test.HUnit
import Test.Tasty.TH
import Test.QuickCheck.Arbitrary
import Test.QuickCheck.Gen
import Test.Framework.Providers.HUnit
import Test.Framework.Providers.QuickCheck2
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck

import qualified Data.ByteString.Lazy as BL
import qualified Data.Vector.Storable as VS
Expand Down
7 changes: 3 additions & 4 deletions Tests-Src/Tests/IntGroups.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,10 +3,9 @@ module Tests.IntGroups
( tgroup_IntGroups
) where

import Test.Framework.TH
import Test.Framework.Providers.HUnit
import Test.Framework.Providers.QuickCheck2
import Test.HUnit
import Test.Tasty.TH
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck
import qualified Data.Vector.Unboxed as VU

import qualified Utils.IntGroups as IG
Expand Down
5 changes: 2 additions & 3 deletions Tests-Src/Tests/Language.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,8 @@ module Tests.Language
( tgroup_Language
) where

import Test.Framework.TH
import Test.Framework.Providers.HUnit
import Test.HUnit
import Test.Tasty.TH
import Test.Tasty.HUnit

import Language

Expand Down
5 changes: 2 additions & 3 deletions Tests-Src/Tests/LoadFQDirectory.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,8 @@ module Tests.LoadFQDirectory
( tgroup_LoadFQDirectory
) where

import Test.Framework.TH
import Test.HUnit
import Test.Framework.Providers.HUnit
import Test.Tasty.TH
import Test.Tasty.HUnit

import Control.Monad (forM_)

Expand Down
4 changes: 2 additions & 2 deletions Tests-Src/Tests/NGLessAPI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@ module Tests.NGLessAPI
( tgroup_NGLessAPI
) where

import Test.Framework.TH
import Test.Framework.Providers.HUnit
import Test.Tasty.TH
import Test.Tasty.HUnit

import Language
import NGLess
Expand Down
5 changes: 2 additions & 3 deletions Tests-Src/Tests/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,8 @@ module Tests.Parse
( tgroup_Parse
) where

import Test.Framework.TH
import Test.Framework.Providers.HUnit
import Test.HUnit
import Test.Tasty.TH
import Test.Tasty.HUnit

import Text.Parsec (SourcePos, parse)
import Text.ParserCombinators.Parsec.Prim (GenParser)
Expand Down
5 changes: 2 additions & 3 deletions Tests-Src/Tests/Select.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,8 @@ module Tests.Select
( tgroup_Select
) where

import Test.Framework.TH
import Test.HUnit
import Test.Framework.Providers.HUnit
import Test.Tasty.TH
import Test.Tasty.HUnit
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Builder as BB

Expand Down
5 changes: 2 additions & 3 deletions Tests-Src/Tests/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,8 @@ module Tests.Types
( tgroup_Types
) where

import Test.Framework.TH
import Test.Framework.Providers.HUnit
import Test.HUnit
import Test.Tasty.TH
import Test.Tasty.HUnit
import qualified Data.Text as T

import Tests.Utils
Expand Down
2 changes: 1 addition & 1 deletion Tests-Src/Tests/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ module Tests.Utils
, asTempFile
, testNGLessIO
) where
import Test.HUnit
import Test.Tasty.HUnit
import qualified Data.Text as T
import qualified Data.ByteString as B
import Control.Monad.IO.Class (liftIO)
Expand Down
5 changes: 2 additions & 3 deletions Tests-Src/Tests/Validation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,8 @@ module Tests.Validation
( tgroup_Validation
) where

import Test.Framework.TH
import Test.Framework.Providers.HUnit
import Test.HUnit
import Test.Tasty.TH
import Test.Tasty.HUnit
import Control.Monad
import Data.Either.Combinators (isRight)
import qualified Data.Text as T
Expand Down
8 changes: 3 additions & 5 deletions Tests-Src/Tests/Vector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,9 @@ module Tests.Vector
( tgroup_Vector
) where

import Test.Framework.TH
import Test.Framework.Providers.HUnit
import Test.Framework.Providers.QuickCheck2
import Test.HUnit
import Test.QuickCheck
import Test.Tasty.TH
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck
import qualified Data.Vector as V
import System.IO.Unsafe (unsafePerformIO)

Expand Down
9 changes: 4 additions & 5 deletions Tests-Src/Tests/Write.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,13 @@
{- Copyright 2015 NGLess Authors
{- Copyright 2015-2021 NGLess Authors
- License: MIT
-}
{-# LANGUAGE TemplateHaskell, OverloadedStrings, TupleSections #-}
{-# LANGUAGE TemplateHaskell #-}
module Tests.Write
( tgroup_Write
) where

import Test.Framework.TH
import Test.HUnit
import Test.Framework.Providers.HUnit
import Test.Tasty.TH
import Test.Tasty.HUnit

import Interpretation.Write

Expand Down
9 changes: 9 additions & 0 deletions docs/sources/whatsnew.rst
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,15 @@
What's New (History)
====================

Unreleased
----------

Internal improvements
~~~~~~~~~~~~~~~~~~~~~

- Switched to the tasty testing framework


Version 1.3.0
-------------

Expand Down
8 changes: 4 additions & 4 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -142,11 +142,11 @@ tests:
cpp-options: -DIS_BUILDING_TEST
dependencies:
- HUnit >=1.3
- test-framework >=0.8
- test-framework-hunit
- test-framework-quickcheck2
- test-framework-th
- QuickCheck >=2.8
- tasty
- tasty-hunit
- tasty-quickcheck
- tasty-th
when:
- condition: ! '!(flag(embed))'
then:
Expand Down

0 comments on commit 19a7fbd

Please sign in to comment.