Skip to content
Snippets Groups Projects
Commit b1a297e5 authored by Eduardo Trujillo's avatar Eduardo Trujillo
Browse files

feat(Parsers): Improve handling of Breaking Changes blocks

parent f46c4a52
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE ApplicativeDo #-}
module Shift.Parsers where
......@@ -34,6 +35,7 @@ import Text.Megaparsec
(<|>),
)
import Text.Megaparsec.Char (char, eol, spaceChar, string)
import Control.Applicative (optional)
type Parser = Parsec Void Text
......@@ -113,9 +115,11 @@ breakingChange :: Parser BreakingChange
breakingChange = do
void . spaced . string $ "BREAKING CHANGE: "
BreakingChange
<$> (cs <$> manyCharsTill eol)
<*> (cs <$> manyCharsTill (spaced eof <|> (skipSome ticketChange *> eof)))
do
shortDescription <- cs <$> manyCharsTill eol
body <- optional (cs <$> (void eol *> someCharsTill (try (spaced eof <|> (skipSome ticketChange *> eof)))))
return $ BreakingChange shortDescription body
ticketChange :: Parser (HashSet TicketChange)
ticketChange = do
......
......@@ -76,9 +76,9 @@ instance Exception ShiftException
type TicketChange = (Text, Text)
data MergeCommit = MergeCommit Text deriving (Show)
data MergeCommit = MergeCommit Text deriving (Show, Eq)
data MiscCommit = MiscCommit Text deriving (Show)
data MiscCommit = MiscCommit Text deriving (Show, Eq)
data CommitType
= CTFeature
......@@ -92,9 +92,9 @@ data CommitType
data BreakingChange = BreakingChange
{ _bcSubject :: Text,
_bcBody :: Text
_bcBody :: Maybe Text
}
deriving (Show)
deriving (Show, Eq)
data ConventionalCommit = ConventionalCommit
{ _ccType :: CommitType,
......@@ -104,7 +104,7 @@ data ConventionalCommit = ConventionalCommit
_ccBreakingChanges :: [BreakingChange],
_ccAffectedTickets :: [HashSet TicketChange]
}
deriving (Show)
deriving (Show, Eq)
data TagRef = TagRef
{ _tRef :: RefName,
......@@ -119,7 +119,7 @@ data ParsedCommit
= PCConventional ConventionalCommit
| PCMerge MergeCommit
| PCMisc MiscCommit
deriving (Show)
deriving (Show, Eq)
type ParsedGroup hash = (Ref hash, Commit hash, ParsedCommit)
......
......@@ -2,16 +2,98 @@
module Test.Shift.ParsersSpec where
import Shift.Parsers (commitType)
import Shift.Types (CommitType (CTFeature))
import Shift (BreakingChange (BreakingChange))
import Shift.Parsers (breakingChange, commit, commitType, manyCharsTill, someCharsTill, spaced)
import Shift.Types (CommitType (CTFeature), ConventionalCommit (ConventionalCommit, _ccAffectedTickets, _ccBody, _ccBreakingChanges, _ccScope, _ccSubject, _ccType), ParsedCommit (PCConventional))
import Test.Hspec (Spec, describe, it)
import Test.Hspec.Megaparsec (shouldFailOn, shouldParse)
import Text.Megaparsec (parse)
import Text.Megaparsec.Char (eol, string)
spec :: Spec
spec = do
-- spaced
describe "spaced" $ do
it "parses using the inner parser" $ do
parse (spaced $ string "hello") "" "hello" `shouldParse` "hello"
it "parses using the inner parser (with whitespace)" $ do
parse (spaced $ string "hello") "" " hello" `shouldParse` "hello"
it "parses using the inner parser (with newlines)" $ do
parse (spaced $ string "hello") "" "\n\n\nhello" `shouldParse` "hello"
it "parses using the inner parser (with newlines and whitespace)" $ do
parse (spaced $ string "hello") "" "\n \n \nhello" `shouldParse` "hello"
-- manyCharsTill
describe "manyCharsTill" $ do
it "parses empty strings (with EOL)" $ do
parse (manyCharsTill eol) "" "\n" `shouldParse` ""
it "parses strings (with EOL)" $ do
parse (manyCharsTill eol) "" "hello\n" `shouldParse` "hello"
it "fails on empty strings (without EOL)" $ do
parse (manyCharsTill eol) "" `shouldFailOn` ""
-- someCharsTill
describe "someCharsTill" $ do
it "fails on empty strings (with EOL)" $ do
parse (someCharsTill eol) "" `shouldFailOn` "\n"
it "parses strings (with EOL)" $ do
parse (someCharsTill eol) "" "hello\n" `shouldParse` "hello"
it "fails on empty strings (without EOL)" $ do
parse (someCharsTill eol) "" `shouldFailOn` ""
-- commitType
describe "commitType" $ do
it "parses a commit type" $ do
parse commitType "" "feat" `shouldParse` CTFeature
it "should fail if the commit type is unknown" $ do
parse commitType "" `shouldFailOn` "omg"
-- breakingChange
describe "breakingChange" $ do
it "parses a breaking change without a body" $ do
parse
breakingChange
""
"BREAKING CHANGE: This will require a new OS upgrade.\n"
`shouldParse` BreakingChange "This will require a new OS upgrade." Nothing
it "parses a breaking change with a body" $ do
parse
breakingChange
""
"BREAKING CHANGE: This will require a new OS upgrade.\n\
\\n\
\Go to example.org to download a new OS."
`shouldParse` BreakingChange
"This will require a new OS upgrade."
(Just "Go to example.org to download a new OS.")
-- commit
describe "commit" $ do
it "parses a regular commit" $ do
parse commit "" "feat(src): Add README file"
`shouldParse` ( PCConventional $
ConventionalCommit
{ _ccType = CTFeature,
_ccScope = "src",
_ccSubject = "Add README file",
_ccBody = "",
_ccBreakingChanges = [],
_ccAffectedTickets = []
}
)
it "parses a regular commit with breaking changes and a body" $ do
parse
commit
""
"feat(src): Add README file\n\
\\n\
\This is an example commit body.\n\
\\n\
\BREAKING CHANGE: This will require a new OS upgrade.\n\
\\n\
\Go to example.org to download a new OS.\n"
`shouldParse` ( PCConventional $
ConventionalCommit
{ _ccType = CTFeature,
_ccScope = "src",
_ccSubject = "Add README file",
_ccBody = "This is an example commit body.",
_ccBreakingChanges = [BreakingChange "This will require a new OS upgrade." (Just "Go to example.org to download a new OS.")],
_ccAffectedTickets = []
}
)
\ No newline at end of file
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