add a few hunit tests for parser

This commit is contained in:
Benno Fünfstück 2014-08-03 14:17:43 +02:00
parent 755f39d3c6
commit 3922112bab
5 changed files with 87 additions and 2 deletions

View File

@ -1,6 +1,6 @@
{-# LANGUAGE CPP #-}
module Nix.Parser (parseNixFile, Result(..)) where
module Nix.Parser (parseNixFile, parseNixString, Result(..)) where
import Control.Applicative
import Control.Monad
@ -170,3 +170,7 @@ lookaheadForSet = do
parseNixFile :: MonadIO m => FilePath -> m (Result NExpr)
parseNixFile = parseFromFileEx nixApp
parseNixString :: String -> Result NExpr
parseNixString = parseFromString nixApp

View File

@ -66,6 +66,9 @@ parseFromFileEx p path =
(either (Failure . text . show) Success . parse p path)
`liftM` liftIO (T.readFile path)
parseFromString :: Parser a -> String -> Result a
parseFromString p = either (Failure . text . show) Success . parse p "<string>" . pack
#else
import Data.Char
@ -73,7 +76,9 @@ import Data.List (nub)
import Data.Text hiding (map)
import Text.Parser.Expression as X
import Text.Parser.LookAhead as X
import Text.Trifecta as X hiding (whiteSpace, symbol, symbolic)
import Text.Trifecta as X hiding (whiteSpace, symbol, symbolic, parseString)
import Text.Trifecta (parseString)
import Text.Trifecta.Delta
identifier :: Parser Text
identifier = pack <$> ((:) <$> letter <*> many (alphaNum <|> oneOf "_."))
@ -137,6 +142,9 @@ inCommentSingle
where
startEnd = nub ("*/" ++ "/*")
parseFromString :: Parser a -> String -> Result a
parseFromString p = parseString p (Directed "<string>" 0 0 0 0)
#endif
reservedNames :: [String]

View File

@ -92,6 +92,19 @@ executable hnix
, trifecta
ghc-options: -Wall
test-suite hnix-tests
type: exitcode-stdio-1.0
hs-source-dirs: tests
default-language: Haskell2010
main-is: Main.hs
build-depends:
base >= 4.3 && < 5
, containers
, hnix
, tasty
, tasty-th
, tasty-hunit
source-repository head
type: git
location: git://github.com/jwiegley/hnix.git

10
tests/Main.hs Normal file
View File

@ -0,0 +1,10 @@
module Main where
import Test.Tasty
import qualified ParserTests
main :: IO ()
main = defaultMain $ testGroup "hnix"
[ ParserTests.tests
]

50
tests/ParserTests.hs Normal file
View File

@ -0,0 +1,50 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-}
module ParserTests (tests) where
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.TH
import Nix.Types
import Nix.Parser
case_constant_int :: Assertion
case_constant_int = assertParseString "234" $ Fix (NConstant (NInt 234))
case_simple_set :: Assertion
case_simple_set = assertParseString "{ a = 23; b = 4; }" $ Fix $ NSet NonRec
[ (Fix (NConstant (NSym "a")), Fix (NConstant (NInt 23)))
, (Fix (NConstant (NSym "b")), Fix (NConstant (NInt 4)))
]
case_int_list :: Assertion
case_int_list = assertParseString "[1 2 3]" $ Fix $ NList
[ Fix (NConstant (NInt i)) | i <- [1,2,3] ]
case_int_null_list :: Assertion
case_int_null_list = assertParseString "[1 2 3 null 4]" $ Fix (NList (map (Fix . NConstant) [NInt 1, NInt 2, NInt 3, NNull, NInt 4]))
case_simple_lambda :: Assertion
case_simple_lambda = assertParseString "a: a" $ Fix (NAbs asym asym) where
asym = Fix (NConstant (NSym "a"))
case_lambda_app_int :: Assertion
case_lambda_app_int = assertParseString "(a:a) 3" $ Fix (NApp lam int) where
int = Fix (NConstant (NInt 3))
lam = Fix (NAbs asym asym)
asym = Fix (NConstant (NSym "a"))
case_simple_let :: Assertion
case_simple_let = assertParseString "let a = 4; in a" $ Fix (NLet binds asym) where
binds = [(asym, Fix (NConstant (NInt 4)))]
asym = Fix (NConstant (NSym "a"))
tests :: TestTree
tests = $testGroupGenerator
--------------------------------------------------------------------------------
assertParseString :: String -> NExpr -> Assertion
assertParseString str expected = case parseNixString str of
Success actual -> assertEqual ("When parsing " ++ str) expected actual
Failure err -> assertFailure $ "Unexpected error parsing `" ++ str ++ "':\n" ++ show err