hnix/tests/TestCommon.hs
Anton-Latukha 0cb3946ee7
clean-up: (return -> pure)
M  main/Main.hs
M  main/Repl.hs
M  src/Nix/Builtins.hs
M  src/Nix/Convert.hs
M  src/Nix/Effects.hs
M  src/Nix/Effects/Basic.hs
M  src/Nix/Eval.hs
M  src/Nix/Exec.hs
M  src/Nix/Expr/Types.hs
M  src/Nix/Json.hs
M  src/Nix/Lint.hs
M  src/Nix/Normal.hs
M  src/Nix/Options/Parser.hs
M  src/Nix/Parser.hs
M  src/Nix/Scope.hs
M  src/Nix/String.hs
M  src/Nix/TH.hs
M  src/Nix/Thunk/Basic.hs
M  src/Nix/Utils.hs
M  src/Nix/Value.hs
M  src/Nix/Value/Equal.hs
M  src/Nix/XML.hs
M  tests/EvalTests.hs
M  tests/Main.hs
M  tests/NixLanguageTests.hs
M  tests/ParserTests.hs
M  tests/TestCommon.hs
2020-09-21 01:57:52 +03:00

80 lines
2.6 KiB
Haskell

{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module TestCommon where
import Control.Monad.Catch
import Control.Monad.IO.Class
import Data.Text ( Text
, unpack
)
import Data.Time
import Nix
import Nix.Exec ( )
import Nix.Standard
import Nix.Fresh.Basic
import System.Environment
import System.IO
import System.Posix.Files
import System.Posix.Temp
import System.Process
import Test.Tasty.HUnit
hnixEvalFile :: Options -> FilePath -> IO (StdValue (StandardT (StdIdT IO)))
hnixEvalFile opts file = do
parseResult <- parseNixFileLoc file
case parseResult of
Failure err ->
error $ "Parsing failed for file `" ++ file ++ "`.\n" ++ show err
Success expr -> do
setEnv "TEST_VAR" "foo"
runWithBasicEffects opts
$ catch (evaluateExpression (Just file) nixEvalExprLoc normalForm expr)
$ \case
NixException frames ->
errorWithoutStackTrace
. show
=<< renderFrames @(StdValue (StandardT (StdIdT IO)))
@(StdThunk (StandardT (StdIdT IO)))
frames
hnixEvalText :: Options -> Text -> IO (StdValue (StandardT (StdIdT IO)))
hnixEvalText opts src = case parseNixText src of
Failure err ->
error
$ "Parsing failed for expression `"
++ unpack src
++ "`.\n"
++ show err
Success expr ->
runWithBasicEffects opts $ normalForm =<< nixEvalExpr Nothing expr
nixEvalString :: String -> IO String
nixEvalString expr = do
(fp, h) <- mkstemp "nix-test-eval"
hPutStr h expr
hClose h
res <- nixEvalFile fp
removeLink fp
pure res
nixEvalFile :: FilePath -> IO String
nixEvalFile fp = readProcess "nix-instantiate" ["--eval", "--strict", fp] ""
assertEvalFileMatchesNix :: FilePath -> Assertion
assertEvalFileMatchesNix fp = do
time <- liftIO getCurrentTime
hnixVal <- (++ "\n") . printNix <$> hnixEvalFile (defaultOptions time) fp
nixVal <- nixEvalFile fp
assertEqual fp nixVal hnixVal
assertEvalMatchesNix :: Text -> Assertion
assertEvalMatchesNix expr = do
time <- liftIO getCurrentTime
hnixVal <- (++ "\n") . printNix <$> hnixEvalText (defaultOptions time) expr
nixVal <- nixEvalString expr'
assertEqual expr' nixVal hnixVal
where expr' = unpack expr