Skip to content

Commit

Permalink
Add tests for the C backend
Browse files Browse the repository at this point in the history
Also refactor the system tests: instead of testing all backends at once
in one test-suite, give each backend its own test suite.
The benefit of that is that we can use flags in cabal to deactivate test
suite if need be
  • Loading branch information
gdetrez committed Mar 6, 2013
1 parent c65bcc1 commit b01220f
Show file tree
Hide file tree
Showing 5 changed files with 258 additions and 78 deletions.
62 changes: 45 additions & 17 deletions source/BNFC.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -160,27 +160,55 @@ Executable bnfc
-- F-sharp
FSharpTop

Test-suite SystemTesting
Flag haskell-tests
Description: Enable debug support
Default: True

Test-suite system-tests-haskell
Type: exitcode-stdio-1.0
Build-Depends: base>=4 && <5,
HUnit, test-framework, test-framework-hunit,
shelly, system-filepath, text
-- --, mtl, directory, array, process, filepath,
-- --HUnit, test-framework, test-framework-hunit
Main-is: SystemTesting.hs
HS-source-dirs: src src/formats test/src
src/formats/haskell2
src/formats/haskell-gadt
src/formats/xml
src/formats/profile
src/formats/java
src/formats/java1.5
src/formats/cpp
src/formats/c
src/formats/ocaml
src/formats/cpp_stl
src/formats/c-sharp
src/formats/f-sharp
Main-is: system-tests-haskell.hs
HS-source-dirs: test/src
if flag(haskell-tests)
Buildable: True
else
Buildable: False


Flag java-tests
Description: Enable debug support
Default: True

Test-suite system-tests-java
Type: exitcode-stdio-1.0
Build-Depends: base>=4 && <5,
HUnit, test-framework, test-framework-hunit,
shelly, system-filepath, text
Main-is: system-tests-java.hs
HS-source-dirs: test/src
if flag(java-tests)
Buildable: True
else
Buildable: False

Flag c-tests
Description: Enable debug support
Default: True

Test-suite system-tests-c
Type: exitcode-stdio-1.0
Build-Depends: base>=4 && <5,
HUnit, test-framework, test-framework-hunit,
shelly, system-filepath, text
Main-is: system-tests-c.hs
HS-source-dirs: test/src
if flag(c-tests)
Buildable: True
else
Buildable: False


Test-suite unit-tests
Type: exitcode-stdio-1.0
Expand Down
150 changes: 89 additions & 61 deletions source/test/src/SystemTesting.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
module Main where
module SystemTesting where

import Test.HUnit (assertBool, (@=?))
import Test.HUnit (assertBool, (@=?), Assertion)
import Test.Framework (defaultMain, testGroup, Test)
import Test.Framework.Providers.HUnit (testCase)
import Filesystem.Path (basename, filename)
Expand All @@ -20,40 +20,37 @@ default (Text)
-- | First we define the backends that we want to test BNFC with.
-- A backend is defined as its name, a list of options to pass to bnfc
-- and a command that runs the generated test program
data Backend = Backend String Text (String -> Sh ())
backends :: [Backend]
backends =
[ Backend "Haskell" "-haskell" (cmd . decodeString . ("./Test" ++))
, Backend "Java" "-java" (\n -> cmd "java" (n </> "Test")) ]

-- data Backend = Backend String Text (String -> Sh ())
-- backends :: [Backend]
-- backends =
-- [ Backend "Haskell" "-haskell" (cmd . decodeString . ("./Test" ++))
-- , Backend "Java" "-java" (\n -> cmd "java" (n </> "Test")) ]
--

-- | Next, we define the test cases: a cf grammar, and an input file
type TestBundle = (FilePath, FilePath)

testName :: TestBundle -> String
testName = encodeString . basename . fst

testGrammar :: TestBundle -> FilePath
testGrammar = fst

testInput :: TestBundle -> FilePath
testInput = snd
testCases :: IO [(FilePath, FilePath)]
testCases = do
dataPath <- shelly $ absPath ("test" </> "data")
return $ map (\(f1,f2) -> (dataPath </> f1, dataPath </> f2))
[ -- ( "alfa/alfa.cf", "alfa/test.alfa" ) Broken
( "c/c.cf", "c/test.c" )
, ( "cpp/cpp.cf", "cpp/test.cpp" )
, ( "gf/gf.cf", "gf/test.gf" )
, ( "lbnf/lbnf.cf", "lbnf/test.lbnf" )
, ( "ocl/ocl.cf", "ocl/test.ocl" ) ]

testCases :: [TestBundle]
testCases = make
[ -- ( "alfa/alfa.cf", "alfa/test.alfa" ) Broken
( "c/c.cf", "c/test.c" )
, ( "cpp/cpp.cf", "cpp/test.cpp" )
, ( "gf/gf.cf", "gf/test.gf" )
, ( "lbnf/lbnf.cf", "lbnf/test.lbnf" )
, ( "ocl/ocl.cf", "ocl/test.ocl" ) ]
where make = map (\(f1,f2) -> ("test/data" </> f1, "test/data" </> f2))

main = testFactory >>= defaultMain
systemTestMain :: Backend -> IO ()
systemTestMain backend = testFactory backend >>= defaultMain

-- | Build The Test Suite
testFactory :: IO [Test]
testFactory = do
testFactory :: Backend -> IO [Test]
testFactory backend = do
-- first we have to find where bnfc is. To do that,
-- we use the getBinDir exposed by cabal and turn the returned
-- string in a FilePath. Then we concatenate “bnfc” to this
Expand All @@ -63,44 +60,75 @@ testFactory = do
-- it looks like cabal doesn't set the binbir variable proserly
-- when running tests. We need to but the hard coded path instead.
bnfcPath <- shelly $ absPath ( "dist"</>"build"</>"bnfc"</>"bnfc")
let bnfc = cmd bnfcPath
cases <- testCases
-- Then we build a list of test groups (one for each backend)
-- using the List monad
return $ do
bknd@(Backend name _ _) <- backends
let tests = [mkTest bnfc bknd tc | tc <- testCases]
return (testGroup name tests)

type BNFC = Text -> Text -> FilePath -> Sh Text

mkTest :: BNFC -> Backend -> TestBundle -> Test
mkTest bnfc (Backend name language runner) bundle = testCase (testName bundle) $
shelly $ print_commands True $
withTmpDir $ \temp -> do
-- Preconditions: thesting for the existence of the input files
assertExists (testGrammar bundle)
assertExists (testInput bundle)
-- Read the test file. We need to do it before cd-ing to the temp
-- directory just in case the path to the file is not absolute.
input <- readfile (testInput bundle)
-- for the same reasons (relative path) we copy the cf file to the
-- temp directory
cp (testGrammar bundle) temp
-- now we can move to the temporary directory
cd temp
let cfFile = filename (testGrammar bundle)
-- we run bnfc and make to build the test programme
bnfc "-m" language cfFile
make
-- Now we run the test programme, passing the content of
-- the test source file on stdin
-- Note that we don't print stdout because it can be very verbose
-- and we only rely on the status code returned by the test
-- program to decide if the test passes or fails
setStdin input
print_stdout False $ runner (testName bundle)
where make = cmd "make"

return $ do
testC <- cases
let name = testName testC
let (cf,test) = testC
return $ testCase name (backend bnfcPath cf test)

-- type BNFC = Text -> Text -> FilePath -> Sh Text
--

-- | A backend test the given test file (source code corresponding to the
-- grammar) given a grammar and a binary of bnfc.
-- All path can be assumed to be absolute.
type Backend = FilePath -- ^ Path to the bnfc binary under test
-> FilePath -- ^ Path to the cf grammar
-> FilePath -- ^ Path to the test file
-> Assertion -- ^ Test result as a HUnit Assertion

-- cBAckend :: Backend
-- cBackend bnfcBin cfFile testFile =
-- shelly $ print_commands True $ withTmpDir $ \temp -> do
-- cd temp
-- -- Preconditions: thesting for the existence of the input files
-- assertExists cfFile
-- assertExists testFile
-- -- TODO test existance and executability of bnf
-- bnfc "-m" "-c" cfFile
-- make
-- -- Now we run the test programme, passing the content of
-- -- the test source file on stdin
-- -- Note that we don't print stdout because it can be very verbose
-- -- and we only rely on the status code returned by the test
-- -- program to decide if the test passes or fails
-- readFile testFile >>= setStdin
-- cmd "./test"
-- where make = cmd "make"
-- bnfc = cmd bnfcBin
--
--
-- mkTest :: BNFC -> Backend -> TestBundle -> Test
-- mkTest bnfc (Backend name language runner) bundle = testCase (testName bundle) $
-- shelly $ print_commands True $
-- withTmpDir $ \temp -> do
-- -- Preconditions: thesting for the existence of the input files
-- assertExists (testGrammar bundle)
-- assertExists (testInput bundle)
-- -- Read the test file. We need to do it before cd-ing to the temp
-- -- directory just in case the path to the file is not absolute.
-- input <- readfile (testInput bundle)
-- -- for the same reasons (relative path) we copy the cf file to the
-- -- temp directory
-- cp (testGrammar bundle) temp
-- -- now we can move to the temporary directory
-- cd temp
-- let cfFile = filename (testGrammar bundle)
-- -- we run bnfc and make to build the test programme
-- bnfc "-m" language cfFile
-- make
-- -- Now we run the test programme, passing the content of
-- -- the test source file on stdin
-- -- Note that we don't print stdout because it can be very verbose
-- -- and we only rely on the status code returned by the test
-- -- program to decide if the test passes or fails
-- setStdin input
-- print_stdout False $ runner (testName bundle)
-- where make = cmd "make"
--

-- HUnit assertion: file exists
assertExists :: FilePath -> Sh ()
Expand Down
41 changes: 41 additions & 0 deletions source/test/src/system-tests-c.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,41 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
module Main where

import Filesystem.Path (basename)
import Filesystem.Path.CurrentOS (decodeString, encodeString)
import Text.Printf (printf)
import Shelly
import Prelude hiding (FilePath)
import Data.Text.Lazy (Text)
import Control.Exception (assert)
import Paths_BNFC
import SystemTesting (systemTestMain, Backend, assertExists)

default (Text)

cBackend :: Backend
cBackend bnfcBin cfFile testFile =
shelly $ print_commands True $ withTmpDir $ \temp -> do
cd temp
-- Preconditions: testing for the existence of the input files
assertExists cfFile
assertExists testFile
-- TODO test existance and executability of bnf
bnfc "-m" "-c" cfFile
make
-- Now we run the test programme, passing the content of
-- the test source file on stdin
-- Note that we don't print stdout because it can be very verbose
-- and we only rely on the status code returned by the test
-- program to decide if the test passes or fails
readfile testFile >>= setStdin
test
where make = cmd "make"
bnfc = cmd bnfcBin
testProg = decodeString ("Test" ++ (encodeString $ basename cfFile))
test = cmd ("." </> testProg)

-- Main is defined in SystemTesting, we just pass our backend as a parameter
main = systemTestMain cBackend
41 changes: 41 additions & 0 deletions source/test/src/system-tests-haskell.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,41 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
module Main where

import Filesystem.Path (basename)
import Filesystem.Path.CurrentOS (decodeString, encodeString)
import Text.Printf (printf)
import Shelly
import Prelude hiding (FilePath)
import Data.Text.Lazy (Text)
import Control.Exception (assert)
import Paths_BNFC
import SystemTesting (systemTestMain, Backend, assertExists)

default (Text)

haskellBackend :: Backend
haskellBackend bnfcBin cfFile testFile =
shelly $ print_commands True $ withTmpDir $ \temp -> do
cd temp
-- Preconditions: testing for the existence of the input files
assertExists cfFile
assertExists testFile
-- TODO test existance and executability of bnf
bnfc "-m" "-haskell" cfFile
make
-- Now we run the test programme, passing the content of
-- the test source file on stdin
-- Note that we don't print stdout because it can be very verbose
-- and we only rely on the status code returned by the test
-- program to decide if the test passes or fails
readfile testFile >>= setStdin
test
where make = cmd "make"
bnfc = cmd bnfcBin
testProg = decodeString ("Test" ++ (encodeString $ basename cfFile))
test = cmd ("." </> testProg)

-- Main is defined in SystemTesting, we just pass our backend as a parameter
main = systemTestMain haskellBackend
42 changes: 42 additions & 0 deletions source/test/src/system-tests-java.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
module Main where

import Filesystem.Path (basename)
import Filesystem.Path.CurrentOS (decodeString, encodeString)
import Text.Printf (printf)
import Shelly
import Prelude hiding (FilePath)
import Data.Text.Lazy (Text)
import Control.Exception (assert)
import Paths_BNFC
import SystemTesting (systemTestMain, Backend, assertExists)

default (Text)

javaBackend :: Backend
javaBackend bnfcBin cfFile testFile =
shelly $ print_commands True $ withTmpDir $ \temp -> do
cd temp
-- Preconditions: testing for the existence of the input files
assertExists cfFile
assertExists testFile
-- TODO test existance and executability of bnf
bnfc "-m" "-java" cfFile
make
-- Now we run the test programme, passing the content of
-- the test source file on stdin
-- Note that we don't print stdout because it can be very verbose
-- and we only rely on the status code returned by the test
-- program to decide if the test passes or fails
readfile testFile >>= setStdin
java testProg
where make = cmd "make"
bnfc = cmd bnfcBin
java = cmd "java"
testProg = basename cfFile </> "Test"

-- Main is defined in SystemTesting, we just pass our backend as a parameter
main = systemTestMain javaBackend

0 comments on commit b01220f

Please sign in to comment.