Skip to content
Snippets Groups Projects
Commit 1128e381 authored by Patrick Augusto's avatar Patrick Augusto
Browse files

Golden testing for standalone test stanza

parent 965db577
No related branches found
No related tags found
No related merge requests found
...@@ -11,7 +11,7 @@ import Test.Tasty.HUnit ...@@ -11,7 +11,7 @@ import Test.Tasty.HUnit
import qualified Data.ByteString.Lazy.Char8 as BS8 import qualified Data.ByteString.Lazy.Char8 as BS8
import Data.List.NonEmpty (fromList) import Data.List.NonEmpty (fromList)
import Data.List.NonEmpty as NEL (NonEmpty) import Data.List.NonEmpty as NEL (NonEmpty, drop)
#if __GLASGOW_HASKELL__ < 804 #if __GLASGOW_HASKELL__ < 804
import Data.Semigroup ((<>)) import Data.Semigroup ((<>))
#endif #endif
...@@ -214,6 +214,16 @@ goldenTestTests v pkgIx pkgDir pkgName = testGroup "test golden tests" ...@@ -214,6 +214,16 @@ goldenTestTests v pkgIx pkgDir pkgName = testGroup "test golden tests"
(goldenTest "test-build-tools-with-comments.golden") $ (goldenTest "test-build-tools-with-comments.golden") $
let opts = WriteOpts False False False v pkgDir Library pkgName defaultCabalVersion let opts = WriteOpts False False False v pkgDir Library pkgName defaultCabalVersion
in runGoldenTest opts testArgs (emptyFlags {buildTools = Flag ["happy"]}) in runGoldenTest opts testArgs (emptyFlags {buildTools = Flag ["happy"]})
, goldenVsString "Standalone tests, empty flags, not simple, no options"
(goldenTest "standalone-test.golden") $
let opts = WriteOpts False False True v pkgDir TestSuite pkgName defaultCabalVersion
in runGoldenTest opts testArgs emptyFlags
, goldenVsString "Standalone tests, empty flags, not simple, with comments + no minimal"
(goldenTest "standalone-test-with-comments.golden") $
let opts = WriteOpts False False False v pkgDir TestSuite pkgName defaultCabalVersion
in runGoldenTest opts testArgs emptyFlags
] ]
where where
runGoldenTest opts args flags = runGoldenTest opts args flags =
...@@ -245,6 +255,14 @@ goldenCabalTests v pkgIx srcDb = testGroup ".cabal file golden tests" ...@@ -245,6 +255,14 @@ goldenCabalTests v pkgIx srcDb = testGroup ".cabal file golden tests"
, goldenVsString "Library, empty flags, not simple, no comments + no minimal" , goldenVsString "Library, empty flags, not simple, no comments + no minimal"
(goldenCabal "cabal-lib-no-comments.golden") $ (goldenCabal "cabal-lib-no-comments.golden") $
runGoldenTest (libProjArgs "N") emptyFlags runGoldenTest (libProjArgs "N") emptyFlags
, goldenVsString "Test suite, empty flags, not simple, with comments + no minimal"
(goldenCabal "cabal-test-suite-with-comments.golden") $
runGoldenTest (testProjArgs "Y") emptyFlags
, goldenVsString "Test suite, empty flags, not simple, no comments + no minimal"
(goldenCabal "cabal-test-suite-no-comments.golden") $
runGoldenTest (testProjArgs "N") emptyFlags
] ]
where where
runGoldenTest args flags = runGoldenTest args flags =
...@@ -265,6 +283,12 @@ goldenCabalTests v pkgIx srcDb = testGroup ".cabal file golden tests" ...@@ -265,6 +283,12 @@ goldenCabalTests v pkgIx srcDb = testGroup ".cabal file golden tests"
testStanza = mkTestStanza opts $ testTarget {_testDependencies = mangleBaseDep testTarget _testDependencies} testStanza = mkTestStanza opts $ testTarget {_testDependencies = mangleBaseDep testTarget _testDependencies}
mkStanza $ pkgFields ++ [libStanza, testStanza] mkStanza $ pkgFields ++ [libStanza, testStanza]
(Right (ProjectSettings opts pkgDesc Nothing Nothing (Just testTarget), _)) -> do
let pkgFields = mkPkgDescription opts pkgDesc
testStanza = mkTestStanza opts $ testTarget {_testDependencies = mangleBaseDep testTarget _testDependencies}
mkStanza $ pkgFields ++ [testStanza]
(Right (ProjectSettings _ _ l e t, _)) -> assertFailure $ (Right (ProjectSettings _ _ l e t, _)) -> assertFailure $
show l ++ "\n" ++ show e ++ "\n" ++ show t show l ++ "\n" ++ show e ++ "\n" ++ show t
...@@ -319,6 +343,12 @@ pkgArgs = fromList ...@@ -319,6 +343,12 @@ pkgArgs = fromList
, "4" , "4"
] ]
testProjArgs :: String -> NonEmpty String
testProjArgs comments = fromList ["4", "foo-package"]
<> pkgArgs
<> fromList (NEL.drop 1 testArgs)
<> fromList [comments]
libProjArgs :: String -> NonEmpty String libProjArgs :: String -> NonEmpty String
libProjArgs comments = fromList ["1", "foo-package"] libProjArgs comments = fromList ["1", "foo-package"]
<> pkgArgs <> pkgArgs
......
cabal-version: 3.0
name: y
version: 0.1.0.0
synopsis: synopsis
-- A longer description of the package.
-- description:
homepage: home
license: BSD-3-Clause
license-file: LICENSE
author: foo-kmett
maintainer: foo-kmett@kmett.kmett
-- A copyright notice.
-- copyright:
category: Data
build-type: Simple
extra-doc-files: CHANGELOG.md
-- Extra source files to be distributed with the package, such as examples, or a tutorial module.
-- extra-source-files:
test-suite y-test
default-language: Haskell2010
-- Modules included in this executable, other than Main.
-- other-modules:
-- LANGUAGE extensions used by modules in this package.
-- other-extensions:
type: exitcode-stdio-1.0
hs-source-dirs: test
main-is: Main.hs
build-depends: base
cabal-version: 3.0
-- Initial package description 'y' generated by
-- 'cabal init'. For further documentation, see:
-- http://haskell.org/cabal/users-guide/
--
-- The name of the package.
name: y
-- The package version.
-- See the Haskell package versioning policy (PVP) for standards
-- guiding when and how versions should be incremented.
-- https://pvp.haskell.org
-- PVP summary: +-+------- breaking API changes
-- | | +----- non-breaking API additions
-- | | | +--- code changes with no API change
version: 0.1.0.0
-- A short (one-line) description of the package.
synopsis: synopsis
-- A longer description of the package.
-- description:
-- URL for the project homepage or repository.
homepage: home
-- The license under which the package is released.
license: BSD-3-Clause
-- The file containing the license text.
license-file: LICENSE
-- The package author(s).
author: foo-kmett
-- An email address to which users can send suggestions, bug reports, and patches.
maintainer: foo-kmett@kmett.kmett
-- A copyright notice.
-- copyright:
category: Data
build-type: Simple
-- Extra doc files to be distributed with the package, such as a CHANGELOG or a README.
extra-doc-files: CHANGELOG.md
-- Extra source files to be distributed with the package, such as examples, or a tutorial module.
-- extra-source-files:
test-suite y-test
-- Base language which the package is written in.
default-language: Haskell2010
-- Modules included in this executable, other than Main.
-- other-modules:
-- LANGUAGE extensions used by modules in this package.
-- other-extensions:
-- The interface type and version of the test suite.
type: exitcode-stdio-1.0
-- Directories containing source files.
hs-source-dirs: test
-- The entrypoint to the test suite.
main-is: Main.hs
-- Test dependencies.
build-depends: base
test-suite y-test
-- Base language which the package is written in.
default-language: Haskell2010
-- Modules included in this executable, other than Main.
-- other-modules:
-- LANGUAGE extensions used by modules in this package.
-- other-extensions:
-- The interface type and version of the test suite.
type: exitcode-stdio-1.0
-- Directories containing source files.
hs-source-dirs: test
-- The entrypoint to the test suite.
main-is: Main.hs
-- Test dependencies.
build-depends: base
test-suite y-test
default-language: Haskell2010
-- Modules included in this executable, other than Main.
-- other-modules:
-- LANGUAGE extensions used by modules in this package.
-- other-extensions:
type: exitcode-stdio-1.0
hs-source-dirs: test
main-is: Main.hs
build-depends: base
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment