Test NSelect reduction

This commit is contained in:
Félix Baylac-Jacqué 2018-06-25 12:55:05 +02:00
parent 32fa31353c
commit 721ddd4f53
No known key found for this signature in database
GPG Key ID: EFD315F31848DBA4
3 changed files with 38 additions and 1 deletions

View File

@ -623,6 +623,7 @@ test-suite hnix-tests
ParserTests
PrettyParseTests
PrettyTests
ReduceExprTests
TestCommon
Paths_hnix
hs-source-dirs:

View File

@ -26,6 +26,7 @@ import Nix.Value
import qualified NixLanguageTests
import qualified ParserTests
import qualified PrettyTests
import qualified ReduceExprTests
-- import qualified PrettyParseTests
import System.Directory
import System.Environment
@ -98,7 +99,8 @@ main = do
| isJust hpackTestsEnv ] ++
[ ParserTests.tests
, EvalTests.tests
, PrettyTests.tests ] ++
, PrettyTests.tests
, ReduceExprTests.tests] ++
-- [ PrettyParseTests.tests
-- (fromIntegral (read (fromMaybe "0" prettyTestsEnv) :: Int)) ] ++
[ evalComparisonTests ] ++

34
tests/ReduceExprTests.hs Normal file
View File

@ -0,0 +1,34 @@
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module ReduceExprTests (tests) where
import Data.Fix
import Test.Tasty
import Test.Tasty.HUnit
import Nix.Atoms
import Nix.Expr.Types
import Nix.Expr.Types.Annotated
import Nix.Reduce (reduceExpr)
import Nix.Parser
tests :: TestTree
tests = testGroup "Expr Reductions"
[ testCase "Non nested NSelect on set should be reduced" $
cmpReduceResult nonNestedSelect nonNestedSelectExpect
]
cmpReduceResult :: Result NExprLoc -> NExpr -> Assertion
cmpReduceResult r e = do
r <- assertSucc r
r <- stripAnnotation <$> reduceExpr Nothing r
r @?= e
where
assertSucc (Success a) = pure a
assertSucc (Failure d) = assertFailure $ show d
nonNestedSelect :: Result NExprLoc
nonNestedSelect = parseNixTextLoc "{a=42;}.a"
nonNestedSelectExpect :: NExpr
nonNestedSelectExpect = Fix . NConstant $ NInt 42