Merge pull request #59 from rimmington/dollar-quoting

Dollar quoting
This commit is contained in:
John Wiegley 2017-05-31 10:54:27 -07:00 committed by GitHub
commit b1a04469bb
4 changed files with 33 additions and 1 deletions

View file

@ -70,7 +70,7 @@ prettyString (Indented parts)
f ([Plain t] : xs) | Text.null (strip t) = xs
f xs = xs
prettyLine = hcat . map prettyPart
prettyPart (Plain t) = text . unpack . replace "$" "''$" . replace "''" "'''" $ t
prettyPart (Plain t) = text . unpack . replace "${" "''${" . replace "''" "'''" $ t
prettyPart (Antiquoted r) = text "$" <> braces (withoutParens r)
prettyParams :: Params NixDoc -> Doc

View file

@ -107,6 +107,8 @@ Test-suite hnix-tests
Other-modules:
ParserTests
EvalTests
ShorthandTests
PrettyTests
Build-depends:
base >= 4.3 && < 5
, containers

View file

@ -5,6 +5,7 @@ import Test.Tasty
import qualified ParserTests
import qualified EvalTests
import qualified ShorthandTests
import qualified PrettyTests
import Prelude (IO, ($))
@ -13,4 +14,5 @@ main = defaultMain $ testGroup "hnix"
[ ParserTests.tests
, EvalTests.tests
, ShorthandTests.tests
, PrettyTests.tests
]

28
tests/PrettyTests.hs Normal file
View file

@ -0,0 +1,28 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-}
module PrettyTests (tests) where
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH
import Nix.Expr
import Nix.Pretty
case_indented_antiquotation :: Assertion
case_indented_antiquotation = do
assertPretty (mkIndentedStr "echo $foo") "''echo $foo''"
assertPretty (mkIndentedStr "echo ${foo}") "''echo ''${foo}''"
case_string_antiquotation :: Assertion
case_string_antiquotation = do
-- TODO: plain $ doesn't need to be escaped here either
assertPretty (mkStr "echo $foo") "\"echo \\$foo\""
assertPretty (mkStr "echo ${foo}") "\"echo \\${foo}\""
tests :: TestTree
tests = $testGroupGenerator
--------------------------------------------------------------------------------
assertPretty :: NExpr -> String -> Assertion
assertPretty e s = assertEqual ("When pretty-printing " ++ show e) s . show $ prettyNix e