hnix/tests/EvalTests.hs
Georges Dubus b61b5791bb Change the environment in evaluation to be a Map Text (NValue m)
Currently, the environment is passed as a `NValue m`, but is assumed to be
a set every single time it is used. This commit changes it `Map Text (NValue
m)`. Since this is used a lot, it defines a new type alias:

```
type ValueSet m = Map.Map Text (NValue m)
```

This has multiples benefits:
- Simplify some code by removing all the checks that the env is indeed a set
- Simplify the usage of the module by making clear that we need a set as the
  environment. (I especially like this, since it took me a while to figure out
  what that argument was supposed to be the first time).
- Make it simple to inject functions in the environment (for example to have
  builtins) since now the function definition doesn't need to unwrap the set.
2018-01-28 23:27:33 +01:00

52 lines
1.3 KiB
Haskell

{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-}
module EvalTests (tests) where
import Data.Fix
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH
import Nix.Eval
import Nix.Parser
import Nix.Expr
import Data.Monoid (Monoid(..))
import Prelude (String)
case_basic_sum :: Assertion
case_basic_sum = constantEqualStr "2" "1 + 1"
case_basic_function :: Assertion
case_basic_function = constantEqualStr "2" "(a: a) 2"
case_set_attr :: Assertion
case_set_attr = constantEqualStr "2" "{ a = 2; }.a"
case_function_set_arg :: Assertion
case_function_set_arg = constantEqualStr "2" "({ a }: 2) { a = 1; }"
case_function_set_two_arg :: Assertion
case_function_set_two_arg = constantEqualStr "2" "({ a, b ? 3 }: b - a) { a = 1; }"
-- case_function_set_two_arg_default_scope :: Assertion
-- case_function_set_two_arg_default_scope = constantEqualStr "2" "({ a, b ? a * 3 }: b - a) { a = 1; }"
tests :: TestTree
tests = $testGroupGenerator
-----------------------
constantEqual :: NExpr -> NExpr -> Assertion
constantEqual a b = do
Fix (NVConstant a') <- evalExpr a mempty
Fix (NVConstant b') <- evalExpr b mempty
assertEqual "" a' b'
constantEqualStr :: String -> String -> Assertion
constantEqualStr a b =
let Success a' = parseNixString a
Success b' = parseNixString b
in constantEqual a' b'