1
1
mirror of https://github.com/github/semantic.git synced 2024-12-30 10:27:45 +03:00

Merge pull request #1196 from github/markdown-headings

Handle === style markdown headings
This commit is contained in:
Timothy Clem 2017-07-12 08:27:12 -07:00 committed by GitHub
commit 13644ca4c1
5 changed files with 13 additions and 7 deletions

View File

@ -23,7 +23,7 @@ newtype Paragraph a = Paragraph [a]
instance Eq1 Paragraph where liftEq = genericLiftEq
instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec
data Section a = Section { sectionHeading :: a, sectionContent :: [a] }
data Section a = Section { sectionLevel :: Int, sectionHeading :: a, sectionContent :: [a] }
deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
instance Eq1 Section where liftEq = genericLiftEq

View File

@ -70,7 +70,7 @@ item :: Assignment
item = makeTerm <$> symbol Item <*> children (many blockElement)
section :: Assignment
section = makeTerm <$> symbol Heading <*> (heading >>= \ headingTerm -> Markup.Section headingTerm <$> while (((<) `on` level) headingTerm) blockElement)
section = makeTerm <$> symbol Heading <*> (heading >>= \ headingTerm -> Markup.Section (level headingTerm) headingTerm <$> while (((<) `on` level) headingTerm) blockElement)
where heading = makeTerm <$> symbol Heading <*> (project (\ ((CMark.HEADING level :. _) :< _) -> Markup.Heading level) <*> children (many inlineElement))
level term = case term of
_ | Just section <- prj (unwrap term) -> level (Markup.sectionHeading section)

View File

@ -80,7 +80,7 @@ isValidSummary _ = True
data Declaration
= MethodDeclaration { declarationIdentifier :: Text }
| FunctionDeclaration { declarationIdentifier :: Text }
| SectionDeclaration { declarationIdentifier :: Text }
| SectionDeclaration { declarationIdentifier :: Text, declarationLevel :: Int }
| ErrorDeclaration { declarationIdentifier :: Text }
deriving (Eq, Generic, NFData, Show)
@ -123,10 +123,11 @@ markupSectionAlgebra :: (Markup.Section :< fs, Syntax.Error error :< fs, HasFiel
-> Source
-> RAlgebra (TermF (Union fs) (Record fields)) (Term (Union fs) (Record fields)) (Maybe Declaration)
markupSectionAlgebra proxy source r
| Just (Markup.Section (heading, _) _) <- prj (tailF r) = Just $ SectionDeclaration (maybe (getSource heading) (toText . flip Source.slice source . sconcat) (nonEmpty (byteRange . extract <$> toList (unwrap heading))))
| Just (Markup.Section level (heading, _) _) <- prj (tailF r) = Just $ SectionDeclaration (maybe (getSource heading) (firstLine . toText . flip Source.slice source . sconcat) (nonEmpty (byteRange . extract <$> toList (unwrap heading)))) level
| Just (Syntax.Error err) <- prj (tailF r) = Just $ ErrorDeclaration (show (err `asProxyTypeOf` proxy))
| otherwise = Nothing
where getSource = toText . flip Source.slice source . byteRange . extract
where getSource = firstLine . toText . flip Source.slice source . byteRange . extract
firstLine = T.takeWhile (/= '\n')
-- | An entry in a table of contents.
@ -214,7 +215,7 @@ toCategoryName :: Declaration -> Text
toCategoryName declaration = case declaration of
FunctionDeclaration _ -> "Function"
MethodDeclaration _ -> "Method"
SectionDeclaration x -> "Heading " <> show (T.length (T.takeWhile (== '#') x))
SectionDeclaration _ l -> "Heading " <> show l
ErrorDeclaration _ -> "ParseError"
instance Listable Declaration where

View File

@ -152,7 +152,7 @@ spec = parallel $ do
it "summarizes Markdown headings" $ do
blobs <- blobsForPaths (both "markdown/headings.A.md" "markdown/headings.B.md")
output <- runTask (diffBlobPair ToCDiffRenderer blobs)
toS output `shouldBe` ("{\"changes\":{\"test/fixtures/toc/markdown/headings.A.md -> test/fixtures/toc/markdown/headings.B.md\":[{\"span\":{\"start\":[5,1],\"end\":[5,7]},\"category\":\"Heading 2\",\"term\":\"## Two\",\"changeType\":\"added\"}]},\"errors\":{}}\n" :: ByteString)
toS output `shouldBe` ("{\"changes\":{\"test/fixtures/toc/markdown/headings.A.md -> test/fixtures/toc/markdown/headings.B.md\":[{\"span\":{\"start\":[5,1],\"end\":[5,7]},\"category\":\"Heading 2\",\"term\":\"## Two\",\"changeType\":\"added\"},{\"span\":{\"start\":[9,1],\"end\":[10,4]},\"category\":\"Heading 1\",\"term\":\"Final\",\"changeType\":\"added\"}]},\"errors\":{}}\n" :: ByteString)
type Diff' = SyntaxDiff Text (Maybe Declaration ': DefaultFields)

View File

@ -3,3 +3,8 @@
Just some text
## Two
more text
Final
===