Fix the tests

This commit is contained in:
John Wiegley 2018-03-30 02:00:36 -07:00
parent 71b4bf5e8a
commit 8e944cc223
3 changed files with 21 additions and 23 deletions

View file

@ -344,10 +344,7 @@ eval (NApp fun arg) = fun >>= forceThunk >>= \case
args <- buildArgument params =<< arg
traceM $ "Evaluating function application with args: "
++ show (NestedMap [args])
scope <- currentScope
traceM $ "Building function result thunk in scope: "
++ show scope
buildThunk =<< clearScopes (pushScope args (forceThunk =<< f))
clearScopes (pushScope args f)
NVBuiltin _ f -> f =<< arg
_ -> error "Attempt to call non-function"
@ -358,8 +355,8 @@ eval (NAbs params body) = do
-- body are forced during application.
scope <- currentScope
traceM $ "Creating lambda abstraction in scope: " ++ show scope
buildThunk $ NVFunction (deferInScope scope <$> params)
(deferInScope scope body)
buildThunk $ NVFunction (pushScopes scope <$> params)
(pushScopes scope body)
tracingExprEval :: MonadNix m => NExpr -> IO (m (NThunk m))
tracingExprEval =

View file

@ -4,17 +4,14 @@
module EvalTests (tests) where
import Control.Monad.Trans.State
import Data.Fix
import qualified Data.Map as Map
import Data.String.Interpolate
import Nix.Builtins
import Nix.Eval
import Nix.Expr
import Nix.Parser
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH
import Data.String.Interpolate
import Nix.Builtins
import Nix.Eval
import Nix.Expr
import Nix.Parser
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH
case_basic_sum =
constantEqualStr "2" "1 + 1"
@ -79,8 +76,8 @@ instance (Show r, Eq r) => Eq (NValueF m r) where
constantEqual :: NExpr -> NExpr -> Assertion
constantEqual a b = do
a' <- tracingEvalTopLevelExprIO a
b' <- tracingEvalTopLevelExprIO b
a' <- tracingEvalTopLevelExprIO Nothing a
b' <- tracingEvalTopLevelExprIO Nothing b
assertEqual "" a' b'
constantEqualStr :: String -> String -> Assertion

View file

@ -17,8 +17,8 @@ import Nix.Builtins
import Nix.Eval
import Nix.Parser
import Nix.Pretty
import System.FilePath
import System.FilePath.Glob (compile, globDir1)
import System.FilePath.Posix
import Test.Tasty
import Test.Tasty.HUnit
@ -107,11 +107,15 @@ assertEvalFail file = catch eval (\(ErrorCall _) -> return ())
where
eval = do
evalResult <- printNix <$> nixEvalFile file
evalResult `seq` assertFailure $ file ++ " should not evaluate.\nThe evaluation result was `" ++ evalResult ++ "`."
evalResult `seq` assertFailure $
file ++ " should not evaluate.\nThe evaluation result was `"
++ evalResult ++ "`."
nixEvalFile :: FilePath -> IO (NValueNF (Cyclic IO))
nixEvalFile file = do
parseResult <- parseNixFile file
case parseResult of
Failure err -> error $ "Parsing failed for file `" ++ file ++ "`.\n" ++ show err
Success expression -> evalTopLevelExprIO expression
Failure err ->
error $ "Parsing failed for file `" ++ file ++ "`.\n" ++ show err
Success expression ->
evalTopLevelExprIO (Just (takeDirectory file)) expression