hnix/tests/NixLanguageTests.hs

159 lines
6.3 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
2018-04-07 00:24:46 +02:00
module NixLanguageTests (genTests) where
2018-02-09 15:32:53 +01:00
import Control.Arrow ((&&&))
import Control.Exception
2018-04-01 19:55:23 +02:00
import Control.Monad
import Control.Monad.IO.Class
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
2018-05-03 06:32:00 +02:00
import Data.Time
import GHC.Exts
import Nix.Lint
import Nix.Options
import Nix.Parser
import Nix.Pretty
import Nix.Utils
import Nix.XML
import qualified Options.Applicative as Opts
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
import TestCommon
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
-- jww (2018-05-07): Temporarily disable this test until #128 is fixed.
. filter ((/= "eval-okay-path") . takeBaseName)
. 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)
2018-04-09 09:52:10 +02:00
return $ localOption (mkTimeout 2000000)
$ 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) =
2018-05-03 06:32:00 +02:00
testCase (takeFileName basename) $ do
time <- liftIO getCurrentTime
let opts = defaultOptions time
case kind of
["parse", "okay"] -> assertParse opts $ the files
["parse", "fail"] -> assertParseFail opts $ the files
["eval", "okay"] -> assertEval opts files
["eval", "fail"] -> assertEvalFail $ the files
_ -> error $ "Unexpected: " ++ show kind
2018-02-09 15:32:53 +01:00
assertParse :: Options -> FilePath -> Assertion
assertParse _opts file = parseNixFileLoc file >>= \case
Success _expr -> return () -- pure $! runST $ void $ lint opts expr
Failure err ->
assertFailure $ "Failed to parse " ++ file ++ ":\n" ++ show err
2018-02-09 15:32:53 +01:00
assertParseFail :: Options -> FilePath -> Assertion
assertParseFail opts file = do
eres <- parseNixFileLoc file
catch (case eres of
Success expr -> do
_ <- pure $! runST $ void $ lint opts expr
assertFailure $ "Unexpected success parsing `"
++ file ++ ":\nParsed value: " ++ show expr
Failure _ -> return ()) $ \(_ :: SomeException) ->
return ()
2018-02-09 15:32:53 +01:00
assertLangOk :: Options -> FilePath -> Assertion
assertLangOk opts file = do
actual <- printNix <$> hnixEvalFile opts (file ++ ".nix")
expected <- Text.readFile $ file ++ ".exp"
assertEqual "" expected $ Text.pack (actual ++ "\n")
2018-02-09 15:32:53 +01:00
assertLangOkXml :: Options -> FilePath -> Assertion
assertLangOkXml opts file = do
actual <- toXML <$> hnixEvalFile opts (file ++ ".nix")
expected <- Text.readFile $ file ++ ".exp.xml"
assertEqual "" expected $ Text.pack actual
2018-02-09 15:32:53 +01:00
assertEval :: Options -> [FilePath] -> Assertion
2018-05-03 06:32:00 +02:00
assertEval _opts files = do
time <- liftIO getCurrentTime
let opts = defaultOptions time
case delete ".nix" $ sort $ map takeExtensions files of
2018-05-03 06:32:00 +02:00
[] -> () <$ hnixEvalFile opts (name ++ ".nix")
[".exp"] -> assertLangOk opts name
[".exp.xml"] -> assertLangOkXml opts name
2018-04-07 23:33:15 +02:00
[".exp.disabled"] -> return ()
[".exp-disabled"] -> return ()
[".exp", ".flags"] -> do
liftIO $ unsetEnv "NIX_PATH"
flags <- Text.readFile (name ++ ".flags")
2018-04-15 11:22:33 +02:00
let flags' | Text.last flags == '\n' = Text.init flags
| otherwise = flags
2018-05-03 06:32:00 +02:00
case Opts.execParserPure Opts.defaultPrefs (nixOptionsInfo time)
2018-04-15 11:22:33 +02:00
(fixup (map Text.unpack (Text.splitOn " " flags'))) of
Opts.Failure err -> errorWithoutStackTrace $
"Error parsing flags from " ++ name ++ ".flags: "
++ show err
Opts.Success opts' ->
assertLangOk
(opts' { include = include opts' ++
[ "nix=../../../../data/nix/corepkgs"
, "lang/dir4"
, "lang/dir5" ] })
name
Opts.CompletionInvoked _ -> error "unused"
2018-04-07 23:33:15 +02:00
_ -> assertFailure $ "Unknown test type " ++ show files
where
name = "data/nix/tests/lang/"
++ the (map (takeFileName . dropExtensions) files)
2018-02-09 15:32:53 +01:00
fixup ("--arg":x:y:rest) = "--arg":(x ++ "=" ++ y):fixup rest
fixup ("--argstr":x:y:rest) = "--argstr":(x ++ "=" ++ y):fixup rest
fixup (x:rest) = x:fixup rest
fixup [] = []
2018-02-09 15:32:53 +01:00
assertEvalFail :: FilePath -> Assertion
2018-04-07 23:33:15 +02:00
assertEvalFail file = catch ?? (\(_ :: SomeException) -> return ()) $ do
2018-05-03 06:32:00 +02:00
time <- liftIO getCurrentTime
evalResult <- printNix <$> hnixEvalFile (defaultOptions time) file
evalResult `seq` assertFailure $
file ++ " should not evaluate.\nThe evaluation result was `"
++ evalResult ++ "`."