hnix/tests/NixLanguageTests.hs

137 lines
4.9 KiB
Haskell
Raw Normal View History

{-# LANGUAGE LambdaCase #-}
2018-02-09 15:32:53 +01:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
2018-02-09 15:32:53 +01:00
module NixLanguageTests (genTests) where
import Control.Arrow ((&&&))
import Control.Exception
2018-04-01 19:55:23 +02:00
import Control.Monad
import Control.Monad.ST
import Data.List (delete, sort)
import Data.List.Split (splitOn)
import Data.Map (Map)
2018-02-09 15:32:53 +01:00
import qualified Data.Map as Map
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import GHC.Exts
import Nix
import Nix.Monad.Instance
import Nix.Parser
import Nix.Pretty
import Nix.Utils
import Nix.Value
import Nix.XML
import System.Environment
2018-03-30 11:00:36 +02:00
import System.FilePath
import System.FilePath.Glob (compile, globDir1)
import Test.Tasty
import Test.Tasty.HUnit
2018-02-09 15:32:53 +01:00
{-
From (git://nix)/tests/lang.sh we see that
lang/parse-fail-*.nix -> parsing should fail
lang/parse-okay-*.nix -> parsing should succeed
lang/eval-fail-*.nix -> eval should fail
lang/eval-okay-*.{nix,xml} -> eval should succeed,
xml dump should be the same as the .xml
lang/eval-okay-*.{nix,exp} -> eval should succeed,
plain text output should be the same as the .exp
lang/eval-okay-*.{nix,exp,flags} -> eval should succeed,
plain text output should be the same as the .exp,
pass the extra flags to nix-instantiate
NIX_PATH=lang/dir3:lang/dir4 should be in the environment of all
eval-okay-*.nix evaluations
2018-02-09 15:32:53 +01:00
TEST_VAR=foo should be in all the environments # for eval-okay-getenv.nix
-}
groupBy :: Ord k => (v -> k) -> [v] -> Map k [v]
groupBy key = Map.fromListWith (++) . map (key &&& pure)
genTests :: IO TestTree
genTests = do
testFiles <- sort . filter ((/= ".xml") . takeExtension)
<$> globDir1 (compile "*-*-*.*") "data/nix/tests/lang"
2018-04-04 05:54:29 +02:00
let testsByName = groupBy (takeFileName . dropExtensions) testFiles
2018-02-09 15:32:53 +01:00
let testsByType = groupBy testType (Map.toList testsByName)
let testGroups = map mkTestGroup (Map.toList testsByType)
return $ localOption (mkTimeout 100000)
$ testGroup "Nix (upstream) language tests" testGroups
2018-02-09 15:32:53 +01:00
where
testType (fullpath, _files) =
take 2 $ splitOn "-" $ takeFileName fullpath
mkTestGroup (kind, tests) =
testGroup (unwords kind) $ map (mkTestCase kind) tests
mkTestCase kind (basename, files) =
testCase (takeFileName basename) $ case kind of
["parse", "okay"] -> assertParse $ the files
["parse", "fail"] -> assertParseFail $ the files
["eval", "okay"] -> assertEval files
["eval", "fail"] -> assertEvalFail $ the files
_ -> error $ "Unexpected: " ++ show kind
2018-02-09 15:32:53 +01:00
assertParse :: FilePath -> Assertion
assertParse file = parseNixFile file >>= \case
Success expr -> pure $! runST $ void $ lint expr
Failure err ->
assertFailure $ "Failed to parse " ++ file ++ ":\n" ++ show err
2018-02-09 15:32:53 +01:00
assertParseFail :: FilePath -> Assertion
assertParseFail file = do
eres <- parseNixFile file
catch (case eres of
Success expr -> do
_ <- pure $! runST $ void $ lint expr
assertFailure $ "Unexpected success parsing `"
++ file ++ ":\nParsed value: " ++ show expr
Failure _ -> return ()) $ \(_ :: SomeException) ->
return ()
2018-02-09 15:32:53 +01:00
assertLangOk :: FilePath -> Assertion
assertLangOk file = do
actual <- printNix <$> nixEvalFile (file ++ ".nix")
expected <- Text.readFile $ file ++ ".exp"
assertEqual "" expected $ Text.pack (actual ++ "\n")
2018-02-09 15:32:53 +01:00
assertLangOkXml :: FilePath -> Assertion
2018-04-06 00:18:58 +02:00
assertLangOkXml file = do
actual <- toXML <$> nixEvalFile (file ++ ".nix")
expected <- Text.readFile $ file ++ ".exp.xml"
assertEqual "" expected $ Text.pack actual
2018-02-09 15:32:53 +01:00
assertEval :: [FilePath] -> Assertion
assertEval files =
2018-04-04 05:54:29 +02:00
case delete ".nix" $ sort $ map takeExtensions files of
2018-02-09 15:32:53 +01:00
[] -> assertLangOkXml name
[".exp"] -> assertLangOk name
2018-04-04 05:54:29 +02:00
[".exp.disabled"] -> return ()
2018-02-09 15:32:53 +01:00
[".exp-disabled"] -> return ()
[".exp", ".flags"] ->
assertFailure $ "Support for flags not implemented (needed by "
++ name ++ ".nix)."
_ -> assertFailure $ "Unknown test type " ++ show files
2018-02-09 15:32:53 +01:00
where
name = "data/nix/tests/lang/"
++ the (map (takeFileName . dropExtensions) files)
2018-02-09 15:32:53 +01:00
assertEvalFail :: FilePath -> Assertion
assertEvalFail file = catch ?? (\(ErrorCall _) -> return ()) $ do
evalResult <- printNix <$> nixEvalFile file
evalResult `seq` assertFailure $
file ++ " should not evaluate.\nThe evaluation result was `"
++ evalResult ++ "`."
2018-02-09 15:32:53 +01:00
2018-04-01 19:55:23 +02:00
nixEvalFile :: FilePath -> IO (NValueNF (Lazy IO))
nixEvalFile file = do
parseResult <- parseNixFileLoc file
2018-02-09 15:32:53 +01:00
case parseResult of
2018-03-30 11:00:36 +02:00
Failure err ->
error $ "Parsing failed for file `" ++ file ++ "`.\n" ++ show err
Success expression -> do
setEnv "TEST_VAR" "foo"
evalLoc (Just file) expression