From b1a297e5389a3a92bff974d86d73d86050af1893 Mon Sep 17 00:00:00 2001
From: Eduardo Trujillo <ed@chromabits.com>
Date: Sat, 26 Dec 2020 19:24:40 -0800
Subject: [PATCH] feat(Parsers): Improve handling of Breaking Changes blocks

---
 src/Shift/Parsers.hs           | 10 ++--
 src/Shift/Types.hs             | 12 ++---
 test/Test/Shift/ParsersSpec.hs | 86 +++++++++++++++++++++++++++++++++-
 3 files changed, 97 insertions(+), 11 deletions(-)

diff --git a/src/Shift/Parsers.hs b/src/Shift/Parsers.hs
index 3668cce..f13f91f 100644
--- a/src/Shift/Parsers.hs
+++ b/src/Shift/Parsers.hs
@@ -1,5 +1,6 @@
 {-# 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
diff --git a/src/Shift/Types.hs b/src/Shift/Types.hs
index 76a701b..35cf8aa 100644
--- a/src/Shift/Types.hs
+++ b/src/Shift/Types.hs
@@ -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)
 
diff --git a/test/Test/Shift/ParsersSpec.hs b/test/Test/Shift/ParsersSpec.hs
index c2e8ef9..33e9da2 100644
--- a/test/Test/Shift/ParsersSpec.hs
+++ b/test/Test/Shift/ParsersSpec.hs
@@ -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
-- 
GitLab