Refactor test suite (#733)

This moves all of the test suite modules underneath a `Dhall.Test`
module hierarchy instead of clobbering the top-level namespace.
This commit is contained in:
Gabriel Gonzalez 2018-12-03 09:17:53 -08:00 committed by GitHub
parent 9148b35aba
commit 83c4a32e99
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
13 changed files with 84 additions and 81 deletions

View File

@ -384,19 +384,19 @@ Executable dhall
Test-Suite tasty
Type: exitcode-stdio-1.0
Hs-Source-Dirs: tests
Main-Is: Tests.hs
Main-Is: Dhall/Test/Main.hs
GHC-Options: -Wall
Other-Modules:
Format
Import
Lint
Normalization
Parser
QuickCheck
Regression
Tutorial
TypeCheck
Util
Dhall.Test.Format
Dhall.Test.Import
Dhall.Test.Lint
Dhall.Test.Normalization
Dhall.Test.Parser
Dhall.Test.QuickCheck
Dhall.Test.Regression
Dhall.Test.Tutorial
Dhall.Test.TypeCheck
Dhall.Test.Util
Build-Depends:
base >= 4 && < 5 ,
containers ,

View File

@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module Format where
module Dhall.Test.Format where
import Data.Monoid (mempty, (<>))
import Data.Text (Text)
@ -17,8 +17,8 @@ import qualified Dhall.Pretty
import qualified Test.Tasty
import qualified Test.Tasty.HUnit
formatTests :: TestTree
formatTests =
tests :: TestTree
tests =
Test.Tasty.testGroup "format tests"
[ should
Unicode

View File

@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module Import where
module Dhall.Test.Import where
import Data.Text (Text)
import Test.Tasty (TestTree)
@ -16,8 +16,8 @@ import qualified Dhall.Import
import qualified Test.Tasty
import qualified Test.Tasty.HUnit
importTests :: TestTree
importTests =
tests :: TestTree
tests =
Test.Tasty.testGroup "import tests"
[ Test.Tasty.testGroup "import alternatives"
[ shouldFail

View File

@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module Lint where
module Dhall.Test.Lint where
import Data.Monoid (mempty, (<>))
import Data.Text (Text)
@ -16,8 +16,8 @@ import qualified Dhall.Parser
import qualified Test.Tasty
import qualified Test.Tasty.HUnit
lintTests :: TestTree
lintTests =
tests :: TestTree
tests =
Test.Tasty.testGroup "format tests"
[ should
"correctly handle multi-let expressions"

View File

@ -0,0 +1,38 @@
module Main where
import Test.Tasty (TestTree)
import qualified Dhall.Test.Format
import qualified Dhall.Test.Import
import qualified Dhall.Test.Lint
import qualified Dhall.Test.Normalization
import qualified Dhall.Test.Parser
import qualified Dhall.Test.QuickCheck
import qualified Dhall.Test.Regression
import qualified Dhall.Test.Tutorial
import qualified Dhall.Test.TypeCheck
import qualified System.Directory
import qualified System.Environment
import qualified Test.Tasty
import System.FilePath ((</>))
allTests :: TestTree
allTests =
Test.Tasty.testGroup "Dhall Tests"
[ Dhall.Test.Normalization.tests
, Dhall.Test.Parser.tests
, Dhall.Test.Regression.tests
, Dhall.Test.Tutorial.tests
, Dhall.Test.Format.tests
, Dhall.Test.TypeCheck.tests
, Dhall.Test.Import.tests
, Dhall.Test.QuickCheck.tests
, Dhall.Test.Lint.tests
]
main :: IO ()
main = do
pwd <- System.Directory.getCurrentDirectory
System.Environment.setEnv "XDG_CACHE_HOME" (pwd </> ".cache")
Test.Tasty.defaultMain allTests

View File

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
module Normalization (normalizationTests) where
module Dhall.Test.Normalization where
import Data.Monoid ((<>))
import Data.Text (Text)
@ -19,10 +19,10 @@ import Dhall.Core
import Dhall.Context
import Test.Tasty
import Test.Tasty.HUnit
import Util
import Dhall.Test.Util
normalizationTests :: TestTree
normalizationTests =
tests :: TestTree
tests =
testGroup "normalization"
[ tutorialExamples
, preludeExamples

View File

@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module Parser where
module Dhall.Test.Parser where
import Data.Text (Text)
import Test.Tasty (TestTree)
@ -12,8 +12,8 @@ import qualified Dhall.Parser
import qualified Test.Tasty
import qualified Test.Tasty.HUnit
parserTests :: TestTree
parserTests =
tests :: TestTree
tests =
Test.Tasty.testGroup "parser tests"
[ Test.Tasty.testGroup "whitespace"
[ shouldParse

View File

@ -4,7 +4,7 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
module QuickCheck where
module Dhall.Test.QuickCheck where
import Codec.Serialise (DeserialiseFailure(..))
import Control.Monad (guard)
@ -350,9 +350,9 @@ isNormalizedIsConsistentWithNormalize expression =
Dhall.Core.isNormalized expression
=== (Dhall.Core.normalize expression == expression)
quickcheckTests :: TestTree
quickcheckTests
= Test.Tasty.QuickCheck.testProperties
tests :: TestTree
tests =
Test.Tasty.QuickCheck.testProperties
"QuickCheck"
[ ( "Binary serialization should round-trip"
, Test.QuickCheck.property binaryRoundtrip

View File

@ -2,7 +2,7 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Regression where
module Dhall.Test.Regression where
import qualified Control.Exception
import qualified Data.Text.Lazy.IO
@ -14,11 +14,11 @@ import qualified Dhall.Core
import qualified Dhall.Map
import qualified Dhall.Parser
import qualified Dhall.Pretty
import qualified Dhall.Test.Util as Util
import qualified Dhall.TypeCheck
import qualified System.Timeout
import qualified Test.Tasty
import qualified Test.Tasty.HUnit
import qualified Util
import Control.DeepSeq (($!!))
import Dhall.Import (Imported)
@ -27,8 +27,8 @@ import Dhall.TypeCheck (TypeError, X)
import Test.Tasty (TestTree)
import Test.Tasty.HUnit ((@?=))
regressionTests :: TestTree
regressionTests =
tests :: TestTree
tests =
Test.Tasty.testGroup "regression tests"
[ issue96
, issue126

View File

@ -2,13 +2,13 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Tutorial where
module Dhall.Test.Tutorial where
import qualified Data.Vector
import qualified Dhall
import qualified Dhall.Test.Util as Util
import qualified Test.Tasty
import qualified Test.Tasty.HUnit
import qualified Util
import Data.Monoid ((<>))
import Data.Text (Text)
@ -18,8 +18,8 @@ import Numeric.Natural (Natural)
import Test.Tasty (TestTree)
import Test.Tasty.HUnit ((@?=))
tutorialTests :: TestTree
tutorialTests =
tests :: TestTree
tests =
Test.Tasty.testGroup "tutorial"
[ Test.Tasty.testGroup "Interpolation"
[ _Interpolation_0

View File

@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module TypeCheck where
module Dhall.Test.TypeCheck where
import Data.Monoid (mempty, (<>))
import Data.Text (Text)
@ -18,8 +18,8 @@ import qualified Dhall.TypeCheck
import qualified Test.Tasty
import qualified Test.Tasty.HUnit
typecheckTests :: TestTree
typecheckTests =
tests :: TestTree
tests =
Test.Tasty.testGroup "typecheck tests"
[ preludeExamples
, accessTypeChecks

View File

@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
module Util
module Dhall.Test.Util
( code
, codeWith
, equivalent
@ -49,8 +50,8 @@ codeWith ctx expr = do
equivalent :: Text -> Text -> IO ()
equivalent text0 text1 = do
expr0 <- fmap Dhall.Core.normalize (Util.code text0) :: IO (Expr X X)
expr1 <- fmap Dhall.Core.normalize (Util.code text1) :: IO (Expr X X)
expr0 <- fmap Dhall.Core.normalize (code text0) :: IO (Expr X X)
expr1 <- fmap Dhall.Core.normalize (code text1) :: IO (Expr X X)
assertEqual "Expressions are not equivalent" expr0 expr1
assertNormalizesTo :: Expr Src X -> Text -> IO ()

View File

@ -1,36 +0,0 @@
module Main where
import Lint (lintTests)
import Normalization (normalizationTests)
import Parser (parserTests)
import Regression (regressionTests)
import QuickCheck (quickcheckTests)
import Tutorial (tutorialTests)
import TypeCheck (typecheckTests)
import Format (formatTests)
import Import (importTests)
import System.FilePath ((</>))
import Test.Tasty
import qualified System.Directory
import qualified System.Environment
allTests :: TestTree
allTests =
testGroup "Dhall Tests"
[ normalizationTests
, parserTests
, regressionTests
, tutorialTests
, formatTests
, typecheckTests
, importTests
, quickcheckTests
, lintTests
]
main :: IO ()
main = do
pwd <- System.Directory.getCurrentDirectory
System.Environment.setEnv "XDG_CACHE_HOME" (pwd </> ".cache")
defaultMain allTests