Adjust type-checking test setup (#1275)

… in response to https://github.com/dhall-lang/dhall-lang/pull/723.
This commit is contained in:
Simon Jakobi 2019-09-15 04:56:16 +02:00 committed by mergify[bot]
parent 1fed9063d5
commit fddce0b8cf
7 changed files with 133 additions and 233 deletions

@ -1 +1 @@
Subproject commit 7639b4ed2fd457bfa77daabfd329fea3b25581c9 Subproject commit 084ec169695c09e8ac92c4c0dfeb4f9b8188b593

View File

@ -76,6 +76,8 @@ Extra-Source-Files:
dhall-lang/Prelude/List/reverse dhall-lang/Prelude/List/reverse
dhall-lang/Prelude/List/shifted dhall-lang/Prelude/List/shifted
dhall-lang/Prelude/List/unzip dhall-lang/Prelude/List/unzip
dhall-lang/Prelude/Location/package.dhall
dhall-lang/Prelude/Location/Type
dhall-lang/Prelude/Map/Entry dhall-lang/Prelude/Map/Entry
dhall-lang/Prelude/Map/keys dhall-lang/Prelude/Map/keys
dhall-lang/Prelude/Map/map dhall-lang/Prelude/Map/map
@ -97,6 +99,7 @@ Extra-Source-Files:
dhall-lang/Prelude/Natural/package.dhall dhall-lang/Prelude/Natural/package.dhall
dhall-lang/Prelude/Natural/product dhall-lang/Prelude/Natural/product
dhall-lang/Prelude/Natural/show dhall-lang/Prelude/Natural/show
dhall-lang/Prelude/Natural/subtract
dhall-lang/Prelude/Natural/sum dhall-lang/Prelude/Natural/sum
dhall-lang/Prelude/Natural/toDouble dhall-lang/Prelude/Natural/toDouble
dhall-lang/Prelude/Natural/toInteger dhall-lang/Prelude/Natural/toInteger
@ -119,6 +122,8 @@ Extra-Source-Files:
dhall-lang/Prelude/Text/concatMap dhall-lang/Prelude/Text/concatMap
dhall-lang/Prelude/Text/concatMapSep dhall-lang/Prelude/Text/concatMapSep
dhall-lang/Prelude/Text/concatSep dhall-lang/Prelude/Text/concatSep
dhall-lang/Prelude/Text/default
dhall-lang/Prelude/Text/defaultMap
dhall-lang/Prelude/Text/package.dhall dhall-lang/Prelude/Text/package.dhall
dhall-lang/Prelude/Text/show dhall-lang/Prelude/Text/show
dhall-lang/Prelude/XML/attribute dhall-lang/Prelude/XML/attribute
@ -290,128 +295,69 @@ Extra-Source-Files:
dhall-lang/tests/semantic-hash/success/simple/*.hash dhall-lang/tests/semantic-hash/success/simple/*.hash
dhall-lang/tests/semantic-hash/success/simplifications/*.dhall dhall-lang/tests/semantic-hash/success/simplifications/*.dhall
dhall-lang/tests/semantic-hash/success/simplifications/*.hash dhall-lang/tests/semantic-hash/success/simplifications/*.hash
dhall-lang/tests/typecheck/data/*.dhall dhall-lang/tests/type-inference/data/*.dhall
dhall-lang/tests/typecheck/failure/*.dhall dhall-lang/tests/type-inference/failure/*.dhall
dhall-lang/tests/typecheck/success/*.dhall dhall-lang/tests/type-inference/success/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/and/*.dhall dhall-lang/tests/type-inference/success/prelude/Bool/and/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/and/*.dhall dhall-lang/tests/type-inference/success/prelude/Bool/build/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/build/*.dhall dhall-lang/tests/type-inference/success/prelude/Bool/even/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/build/*.dhall dhall-lang/tests/type-inference/success/prelude/Bool/fold/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/even/*.dhall dhall-lang/tests/type-inference/success/prelude/Bool/not/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/even/*.dhall dhall-lang/tests/type-inference/success/prelude/Bool/odd/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/fold/*.dhall dhall-lang/tests/type-inference/success/prelude/Bool/or/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/fold/*.dhall dhall-lang/tests/type-inference/success/prelude/Bool/show/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/not/*.dhall dhall-lang/tests/type-inference/success/prelude/Double/show/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/not/*.dhall dhall-lang/tests/type-inference/success/prelude/Integer/show/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/odd/*.dhall dhall-lang/tests/type-inference/success/prelude/Integer/toDouble/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/odd/*.dhall dhall-lang/tests/type-inference/success/prelude/List/all/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/or/*.dhall dhall-lang/tests/type-inference/success/prelude/List/any/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/or/*.dhall dhall-lang/tests/type-inference/success/prelude/List/build/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/show/*.dhall dhall-lang/tests/type-inference/success/prelude/List/concat/*.dhall
dhall-lang/tests/typecheck/success/prelude/Bool/show/*.dhall dhall-lang/tests/type-inference/success/prelude/List/concatMap/*.dhall
dhall-lang/tests/typecheck/success/prelude/Double/show/*.dhall dhall-lang/tests/type-inference/success/prelude/List/filter/*.dhall
dhall-lang/tests/typecheck/success/prelude/Double/show/*.dhall dhall-lang/tests/type-inference/success/prelude/List/fold/*.dhall
dhall-lang/tests/typecheck/success/prelude/Integer/show/*.dhall dhall-lang/tests/type-inference/success/prelude/List/generate/*.dhall
dhall-lang/tests/typecheck/success/prelude/Integer/show/*.dhall dhall-lang/tests/type-inference/success/prelude/List/head/*.dhall
dhall-lang/tests/typecheck/success/prelude/Integer/toDouble/*.dhall dhall-lang/tests/type-inference/success/prelude/List/indexed/*.dhall
dhall-lang/tests/typecheck/success/prelude/Integer/toDouble/*.dhall dhall-lang/tests/type-inference/success/prelude/List/iterate/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/all/*.dhall dhall-lang/tests/type-inference/success/prelude/List/last/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/all/*.dhall dhall-lang/tests/type-inference/success/prelude/List/length/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/any/*.dhall dhall-lang/tests/type-inference/success/prelude/List/map/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/any/*.dhall dhall-lang/tests/type-inference/success/prelude/List/null/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/build/*.dhall dhall-lang/tests/type-inference/success/prelude/List/replicate/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/build/*.dhall dhall-lang/tests/type-inference/success/prelude/List/reverse/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/concat/*.dhall dhall-lang/tests/type-inference/success/prelude/List/shifted/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/concat/*.dhall dhall-lang/tests/type-inference/success/prelude/List/unzip/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/concatMap/*.dhall dhall-lang/tests/type-inference/success/prelude/Monoid/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/concatMap/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/build/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/filter/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/enumerate/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/filter/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/even/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/fold/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/fold/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/fold/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/isZero/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/generate/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/odd/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/generate/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/product/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/head/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/show/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/head/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/sum/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/indexed/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/toDouble/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/indexed/*.dhall dhall-lang/tests/type-inference/success/prelude/Natural/toInteger/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/iterate/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/all/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/iterate/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/any/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/last/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/build/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/last/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/concat/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/length/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/filter/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/length/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/fold/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/map/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/head/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/map/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/last/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/null/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/length/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/null/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/map/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/replicate/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/null/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/replicate/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/toList/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/reverse/*.dhall dhall-lang/tests/type-inference/success/prelude/Optional/unzip/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/reverse/*.dhall dhall-lang/tests/type-inference/success/prelude/Text/concat/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/shifted/*.dhall dhall-lang/tests/type-inference/success/prelude/Text/concatMap/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/shifted/*.dhall dhall-lang/tests/type-inference/success/prelude/Text/concatMapSep/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/unzip/*.dhall dhall-lang/tests/type-inference/success/prelude/Text/concatSep/*.dhall
dhall-lang/tests/typecheck/success/prelude/List/unzip/*.dhall dhall-lang/tests/type-inference/success/simple/access/*.dhall
dhall-lang/tests/typecheck/success/prelude/Monoid/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/build/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/build/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/enumerate/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/enumerate/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/even/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/even/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/fold/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/fold/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/isZero/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/isZero/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/odd/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/odd/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/product/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/product/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/show/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/show/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/sum/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/sum/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/toDouble/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/toDouble/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/toInteger/*.dhall
dhall-lang/tests/typecheck/success/prelude/Natural/toInteger/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/all/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/all/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/any/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/any/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/build/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/build/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/concat/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/concat/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/filter/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/filter/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/fold/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/fold/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/head/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/head/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/last/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/last/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/length/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/length/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/map/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/map/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/null/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/null/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/toList/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/toList/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/unzip/*.dhall
dhall-lang/tests/typecheck/success/prelude/Optional/unzip/*.dhall
dhall-lang/tests/typecheck/success/prelude/Text/concat/*.dhall
dhall-lang/tests/typecheck/success/prelude/Text/concat/*.dhall
dhall-lang/tests/typecheck/success/prelude/Text/concatMap/*.dhall
dhall-lang/tests/typecheck/success/prelude/Text/concatMap/*.dhall
dhall-lang/tests/typecheck/success/prelude/Text/concatMapSep/*.dhall
dhall-lang/tests/typecheck/success/prelude/Text/concatMapSep/*.dhall
dhall-lang/tests/typecheck/success/prelude/Text/concatSep/*.dhall
dhall-lang/tests/typecheck/success/prelude/Text/concatSep/*.dhall
dhall-lang/tests/typecheck/success/simple/access/*.dhall
dhall-lang/tests/typecheck/success/simple/*.dhall
dhall-lang/tests/type-inference/success/simple/*.dhall dhall-lang/tests/type-inference/success/simple/*.dhall
dhall-lang/tests/type-inference/success/unit/*.dhall dhall-lang/tests/type-inference/success/unit/*.dhall
tests/format/*.dhall tests/format/*.dhall
@ -592,7 +538,6 @@ Test-Suite tasty
Dhall.Test.Regression Dhall.Test.Regression
Dhall.Test.SemanticHash Dhall.Test.SemanticHash
Dhall.Test.Tutorial Dhall.Test.Tutorial
Dhall.Test.TypeCheck
Dhall.Test.TypeInference Dhall.Test.TypeInference
Dhall.Test.Util Dhall.Test.Util
Build-Depends: Build-Depends:

View File

@ -108,7 +108,7 @@ module Dhall.Import (
, hashExpressionToCode , hashExpressionToCode
, writeExpressionToSemanticCache , writeExpressionToSemanticCache
, assertNoImports , assertNoImports
, Status , Status(..)
, SemanticCacheMode(..) , SemanticCacheMode(..)
, Chained , Chained
, chainedImport , chainedImport

View File

@ -14,7 +14,6 @@ import qualified Dhall.Test.Parser
import qualified Dhall.Test.QuickCheck import qualified Dhall.Test.QuickCheck
import qualified Dhall.Test.Regression import qualified Dhall.Test.Regression
import qualified Dhall.Test.Tutorial import qualified Dhall.Test.Tutorial
import qualified Dhall.Test.TypeCheck
import qualified Dhall.Test.TypeInference import qualified Dhall.Test.TypeInference
import qualified GHC.IO.Encoding import qualified GHC.IO.Encoding
import qualified System.Directory import qualified System.Directory
@ -30,8 +29,6 @@ getAllTests = do
formattingTests <- Dhall.Test.Format.getTests formattingTests <- Dhall.Test.Format.getTests
typecheckingTests <- Dhall.Test.TypeCheck.getTests
typeinferenceTests <- Dhall.Test.TypeInference.getTests typeinferenceTests <- Dhall.Test.TypeInference.getTests
importingTests <- Dhall.Test.Import.getTests importingTests <- Dhall.Test.Import.getTests
@ -47,7 +44,6 @@ getAllTests = do
[ normalizationTests [ normalizationTests
, parsingTests , parsingTests
, importingTests , importingTests
, typecheckingTests
, typeinferenceTests , typeinferenceTests
, formattingTests , formattingTests
, lintTests , lintTests

View File

@ -1,92 +0,0 @@
{-# LANGUAGE OverloadedStrings #-}
module Dhall.Test.TypeCheck where
import Control.Exception (SomeException)
import Data.Monoid (mempty, (<>))
import Data.Text (Text)
import Prelude hiding (FilePath)
import Test.Tasty (TestTree)
import Turtle (FilePath, (</>))
import qualified Control.Exception as Exception
import qualified Data.Text as Text
import qualified Dhall.Core as Core
import qualified Dhall.Parser as Parser
import qualified Dhall.Test.Util as Test.Util
import qualified Dhall.TypeCheck as TypeCheck
import qualified Test.Tasty as Tasty
import qualified Test.Tasty.HUnit as Tasty.HUnit
import qualified Turtle
typecheckDirectory :: FilePath
typecheckDirectory = "./dhall-lang/tests/typecheck"
getTests :: IO TestTree
getTests = do
let successTestFiles = Turtle.lstree (typecheckDirectory </> "success")
successTests <- Test.Util.discover (Turtle.chars <* "A.dhall") successTest successTestFiles
let failureTestFiles = Turtle.lstree (typecheckDirectory </> "failure")
failureTests <- Test.Util.discover (Turtle.chars <> ".dhall") failureTest failureTestFiles
let testTree = Tasty.testGroup "typecheck tests"
[ successTests
, failureTests
]
return testTree
successTest :: Text -> TestTree
successTest prefix = do
let skip = []
Test.Util.testCase prefix skip $ do
let actualCode = Test.Util.toDhallPath (prefix <> "A.dhall")
let expectedCode = Test.Util.toDhallPath (prefix <> "B.dhall")
actualExpr <- Core.throws (Parser.exprFromText mempty actualCode )
expectedExpr <- Core.throws (Parser.exprFromText mempty expectedCode)
let annotatedExpr = Core.Annot actualExpr expectedExpr
tryResolvedExpr <- Exception.try (Test.Util.load annotatedExpr)
resolvedExpr <- case tryResolvedExpr of
Left exception -> Tasty.HUnit.assertFailure (show (exception :: SomeException))
Right resolvedExpr -> return resolvedExpr
case TypeCheck.typeOf resolvedExpr of
Left exception -> Tasty.HUnit.assertFailure (show exception)
Right _ -> return ()
{-
_ <- Core.throws (TypeCheck.typeOf resolvedExpr)
-}
return ()
failureTest :: Text -> TestTree
failureTest path = do
let skip = [ typecheckDirectory </> "failure/unit/MergeEmptyNeedsDirectAnnotation1.dhall"
]
Test.Util.testCase path skip $ do
let dhallPath = Test.Util.toDhallPath path
expression <- Core.throws (Parser.exprFromText mempty dhallPath)
let io :: IO Bool
io = do
_ <- Test.Util.load expression
return True
let handler :: SomeException -> IO Bool
handler _ = return False
typeChecked <- Exception.handle handler io
if typeChecked
then Tasty.HUnit.assertFailure (Text.unpack path <> " should not have type-checked")
else return ()

View File

@ -2,12 +2,14 @@
module Dhall.Test.TypeInference where module Dhall.Test.TypeInference where
import Control.Exception (SomeException)
import Data.Monoid (mempty, (<>)) import Data.Monoid (mempty, (<>))
import Data.Text (Text) import Data.Text (Text)
import Prelude hiding (FilePath) import Prelude hiding (FilePath)
import Test.Tasty (TestTree) import Test.Tasty (TestTree)
import Turtle (FilePath, (</>)) import Turtle (FilePath, (</>))
import qualified Control.Exception as Exception
import qualified Data.Text as Text import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO import qualified Data.Text.IO as Text.IO
import qualified Dhall.Core as Core import qualified Dhall.Core as Core
@ -15,6 +17,7 @@ import qualified Dhall.Import as Import
import qualified Dhall.Parser as Parser import qualified Dhall.Parser as Parser
import qualified Dhall.Test.Util as Test.Util import qualified Dhall.Test.Util as Test.Util
import qualified Dhall.TypeCheck as TypeCheck import qualified Dhall.TypeCheck as TypeCheck
import qualified System.FilePath as FilePath
import qualified Test.Tasty as Tasty import qualified Test.Tasty as Tasty
import qualified Test.Tasty.HUnit as Tasty.HUnit import qualified Test.Tasty.HUnit as Tasty.HUnit
import qualified Turtle import qualified Turtle
@ -28,8 +31,13 @@ getTests = do
successTests <- Test.Util.discover (Turtle.chars <* "A.dhall") successTest successTestFiles successTests <- Test.Util.discover (Turtle.chars <* "A.dhall") successTest successTestFiles
let failureTestFiles = Turtle.lstree (typeInferenceDirectory </> "failure")
failureTests <- Test.Util.discover (Turtle.chars <* "A.dhall") failureTest failureTestFiles
let testTree = Tasty.testGroup "type-inference tests" let testTree = Tasty.testGroup "type-inference tests"
[ successTests [ successTests
, failureTests
] ]
return testTree return testTree
@ -44,21 +52,57 @@ successTest prefix = do
] ]
Test.Util.testCase prefix skip $ do Test.Util.testCase prefix skip $ do
value <- expr "A.dhall" let prefixFP = Text.unpack prefix
expectedType <- expr "B.dhall" actualCode <- Text.IO.readFile (prefixFP <> "A.dhall")
inferredType <- case TypeCheck.typeOf value of actualExpr <- Core.throws (Parser.exprFromText mempty actualCode)
tryResolvedExpr <-
Exception.try
(Test.Util.loadRelativeTo
(FilePath.takeDirectory prefixFP)
Import.IgnoreSemanticCache
(Core.denote actualExpr))
resolvedExpr <- case tryResolvedExpr of
Left exception -> Tasty.HUnit.assertFailure (show (exception :: SomeException))
Right resolvedExpr -> return resolvedExpr
expectedTypeCode <- Text.IO.readFile (prefixFP <> "B.dhall")
expectedType <- Core.throws (Parser.exprFromText mempty expectedTypeCode)
resolvedExpectedType <- Import.assertNoImports (Core.denote expectedType)
inferredType <- case TypeCheck.typeOf resolvedExpr of
Left exception -> Tasty.HUnit.assertFailure (show exception) Left exception -> Tasty.HUnit.assertFailure (show exception)
Right inferredType -> return inferredType Right inferredType -> return inferredType
let message = "The inferred type did not match the expected type" let message = "The inferred type did not match the expected type"
Tasty.HUnit.assertEqual message expectedType inferredType Tasty.HUnit.assertEqual message resolvedExpectedType inferredType
where
expr suffix = do
code <- Text.IO.readFile (Text.unpack prefix <> suffix)
e <- Core.throws (Parser.exprFromText mempty code) failureTest :: Text -> TestTree
failureTest path = do
let skip = [ typeInferenceDirectory </> "failure/unit/MergeEmptyNeedsDirectAnnotation1.dhall"
]
Import.assertNoImports (Core.denote e) Test.Util.testCase path skip $ do
let dhallPath = Test.Util.toDhallPath path
expression <- Core.throws (Parser.exprFromText mempty dhallPath)
let io :: IO Bool
io = do
_ <- Test.Util.load expression
return True
let handler :: SomeException -> IO Bool
handler _ = return False
typeChecked <- Exception.handle handler io
if typeChecked
then Tasty.HUnit.assertFailure (Text.unpack path <> " should not have type-checked")
else return ()

View File

@ -7,6 +7,7 @@ module Dhall.Test.Util
, codeWith , codeWith
, equivalent , equivalent
, load , load
, loadRelativeTo
, loadWith , loadWith
, normalize' , normalize'
, normalizeWith' , normalizeWith'
@ -25,7 +26,7 @@ import Data.Bifunctor (first)
import Data.Text (Text) import Data.Text (Text)
import Dhall.Context (Context) import Dhall.Context (Context)
import Dhall.Core (Expr, Normalizer, ReifiedNormalizer(..), Import) import Dhall.Core (Expr, Normalizer, ReifiedNormalizer(..), Import)
import Dhall.Import (Status) import Dhall.Import (Status(..), SemanticCacheMode(..))
import Data.Monoid((<>)) import Data.Monoid((<>))
import Dhall.Parser (Src) import Dhall.Parser (Src)
import Dhall.TypeCheck (X) import Dhall.TypeCheck (X)
@ -44,6 +45,7 @@ import qualified Dhall.Import
import qualified Dhall.Parser import qualified Dhall.Parser
import qualified Dhall.TypeCheck import qualified Dhall.TypeCheck
import qualified Control.Monad.Trans.State.Strict as State import qualified Control.Monad.Trans.State.Strict as State
import qualified System.FilePath as FilePath
import qualified Test.Tasty as Tasty import qualified Test.Tasty as Tasty
import qualified Test.Tasty.ExpectedFailure as Tasty.ExpectedFailure import qualified Test.Tasty.ExpectedFailure as Tasty.ExpectedFailure
import qualified Turtle import qualified Turtle
@ -80,8 +82,13 @@ codeWith ctx expr = do
return expr1 return expr1
load :: Expr Src Import -> IO (Expr Src X) load :: Expr Src Import -> IO (Expr Src X)
load expression = load = loadRelativeTo "." UseSemanticCache
State.evalStateT (loadWith expression) (Dhall.Import.emptyStatus ".")
loadRelativeTo :: FilePath.FilePath -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src X)
loadRelativeTo rootDirectory semanticCacheMode expression =
State.evalStateT
(loadWith expression)
(Dhall.Import.emptyStatus rootDirectory) { _semanticCacheMode = semanticCacheMode }
#ifdef WITH_HTTP #ifdef WITH_HTTP
loadWith :: Expr Src Import -> StateT Status IO (Expr Src X) loadWith :: Expr Src Import -> StateT Status IO (Expr Src X)