hnix/tests/ShorthandTests.hs
Profpatsch 8b4c137a3b Shorthands.hs, mkDot/mkDots: automatically quote non-symbols
Nix can accept (nearly?) arbitrary values as attributes, if they are quoted in
strings. So generating “dots” should always result in valid nix attributes.
This uses the same regex as the nix lexer (as of 1.11).

Also add a few tests whether it correctly generates symbol/non-symbol
attributes.
2017-04-21 03:54:06 +02:00

40 lines
1 KiB
Haskell

{-# LANGUAGE TemplateHaskell, OverloadedStrings #-}
module ShorthandTests (tests) where
import Prelude
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH
import Control.Monad (forM_)
import Data.Monoid ((<>))
import Data.Fix
import Nix.Expr
case_mkDotsSymbolEscaping :: Assertion
case_mkDotsSymbolEscaping = do
let check xs errmsg assert =
forM_ xs $ \x -> assertBool (errmsg <> ": " <> show x) $ assert x
check plain "not a plain value" $ assertIsSingle
check nonPlain "not a non-plain value" $ not . assertIsSingle
where
plain = [ "abc09", "_A_'-", "AbC" ]
nonPlain = [ "abc def", "\\", "'abc", "\"", "-foo", "a.b.c" ]
assertIsSingle = isPlainSingle . getKey . mkDot "dummy"
getKey (Fix (NSelect _ [key] _)) = key
getKey _ = error "invalid"
isPlainSingle (StaticKey _) = True
isPlainSingle (DynamicKey (Plain (DoubleQuoted [Plain _]))) = False
isPlainSingle _ = error "invalid"
---------------------------
tests :: TestTree
tests = $(testGroupGenerator)