Skip to content
Snippets Groups Projects
Commit bac3f60d authored by Oleg Grenrus's avatar Oleg Grenrus
Browse files

Test parsers on travis, fix haddock

parent 9d4dcc9e
No related branches found
No related tags found
No related merge requests found
......@@ -98,7 +98,7 @@ readGenericPackageDescription = readAndParseFile parseGenericPackageDescription
parseGenericPackageDescription :: BS.ByteString -> ParseResult GenericPackageDescription
parseGenericPackageDescription bs = case readFields' bs of
Right (fs, lexWarnings) -> parseGenericPackageDescription' lexWarnings fs
-- | TODO: better marshalling of errors
-- TODO: better marshalling of errors
Left perr -> parseFatalFailure (Position 0 0) (show perr)
runFieldParser :: FieldParser a -> [FieldLine Position] -> ParseResult a
......@@ -124,7 +124,7 @@ fieldlinesToString pos fls =
runFieldParser' :: Position -> FieldParser a -> String -> ParseResult a
runFieldParser' (Position row col) p str = case P.runParser p' [] "<field>" str of
Right (pok, ws) -> do
-- | TODO: map pos
-- TODO: map pos
traverse_ (\(PWarning t pos w) -> parseWarning pos t w) ws
pure pok
Left err -> do
......@@ -161,7 +161,7 @@ parseGenericPackageDescription' lexWarnings fs = do
-> ParseResult (GPDS, GenericPackageDescription)
go (Fields, gpd) (Field (Name pos name) fieldLines) =
case Map.lookup name pdFieldParsers of
-- | TODO: can be more accurate
-- TODO: can be more accurate
Nothing -> fieldlinesToString pos fieldLines >>= \value -> case storeXFieldsPD name value (packageDescription gpd) of
Nothing -> do
parseWarning pos PWTUnknownField $ "Unknown field: " ++ show name
......
......@@ -174,7 +174,7 @@ instance Parsec VersionRange where
P.spaces
return (VersionRangeParens a))
-- | TODO: make those non back-tracking
-- TODO: make those non back-tracking
parseRangeOp (s,f) = P.try (P.string s *> P.spaces *> fmap f parsec)
rangeOps = [ ("<", earlierVersion),
("<=", orEarlierVersion),
......
......@@ -134,5 +134,5 @@ parser = condOr
i <- ident
case P.runParser (p <* P.eof) [] "<ident>" i of
Right x -> pure x
-- | TODO: better lifting or errors / warnings
-- TODO: better lifting or errors / warnings
Left err -> fail $ show err
......@@ -48,7 +48,11 @@ export CABAL_BUILDDIR="${CABAL_BDIR}"
# NB: Best to do everything for a single package together as it's
# more efficient (since new-build will uselessly try to rebuild
# Cabal otherwise).
timed cabal new-build Cabal Cabal:package-tests Cabal:unit-tests
if [ "x$PARSEC" = "xYES" ]; then
timed cabal new-build -fparsec Cabal Cabal:package-tests Cabal:unit-tests Cabal:parser-tests
else
timed cabal new-build Cabal Cabal:package-tests Cabal:unit-tests
fi
# NB: the '|| exit $?' workaround is required on old broken versions of bash
# that ship with OS X. See https://github.com/haskell/cabal/pull/3624 and
......@@ -58,6 +62,10 @@ timed cabal new-build Cabal Cabal:package-tests Cabal:unit-tests
(export CABAL_PACKAGETESTS_DB_STACK="clear:global:${CABAL_STORE_DB}:${CABAL_LOCAL_DB}"; cd Cabal && timed ${CABAL_BDIR}/build/package-tests/package-tests $TEST_OPTIONS) || exit $?
(cd Cabal && timed ${CABAL_BDIR}/build/unit-tests/unit-tests $TEST_OPTIONS) || exit $?
if [ "x$PARSEC" = "xYES" ]; then
(cd Cabal && timed ${CABAL_BDIR}/build/parser-tests/parser-tests $TEST_OPTIONS) || exit $?
fi
# Run haddock (hack: use the Setup script from package-tests!)
(cd Cabal && timed cabal act-as-setup --build-type=Simple -- haddock --builddir=${CABAL_BDIR}) || exit $?
......
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