mirror of
https://github.com/github/semantic.git
synced 2024-11-24 00:42:33 +03:00
Move cmarkParser to its own module.
This commit is contained in:
parent
88865f2c09
commit
4a06d76054
@ -33,6 +33,7 @@ library
|
||||
, Language
|
||||
, Language.C
|
||||
, Language.JavaScript
|
||||
, Language.Markdown
|
||||
, Parser
|
||||
, Patch
|
||||
, Patch.Arbitrary
|
||||
|
@ -4,7 +4,6 @@ module Diffing where
|
||||
import qualified Prologue
|
||||
import Prologue hiding (fst, snd)
|
||||
import Category
|
||||
import CMark
|
||||
import qualified Data.ByteString.Char8 as B1
|
||||
import Data.Functor.Both
|
||||
import Data.Functor.Foldable
|
||||
@ -20,6 +19,7 @@ import Diff
|
||||
import Info
|
||||
import Interpreter
|
||||
import Language
|
||||
import Language.Markdown
|
||||
import Parser
|
||||
import Patch
|
||||
import Range
|
||||
@ -29,7 +29,6 @@ import Renderer.Patch
|
||||
import Renderer.Split
|
||||
import Renderer.Summary
|
||||
import Source
|
||||
import SourceSpan
|
||||
import Syntax
|
||||
import System.Directory
|
||||
import System.FilePath
|
||||
@ -67,31 +66,6 @@ diffFiles parser renderer sourceBlobs = do
|
||||
Leaf s -> Just s
|
||||
_ -> Nothing)
|
||||
|
||||
cmarkParser :: Parser (Syntax Text) (Record '[Range, Category])
|
||||
cmarkParser SourceBlob{..} = pure . toTerm (totalSpan source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source)
|
||||
where toTerm :: SourceSpan -> Node -> Cofree (Syntax Text) (Record '[Range, Category])
|
||||
toTerm within (Node position t children) = let span = maybe within toSpan position in cofree $ (sourceSpanToRange source span .: toCategory t .: RNil) :< case t of
|
||||
-- Leaves
|
||||
CODE text -> Leaf text
|
||||
TEXT text -> Leaf text
|
||||
CODE_BLOCK _ text -> Leaf text
|
||||
-- Branches
|
||||
_ -> Indexed (toTerm span <$> children)
|
||||
|
||||
toCategory :: NodeType -> Category
|
||||
toCategory (TEXT _) = Other "text"
|
||||
toCategory (CODE _) = Other "code"
|
||||
toCategory (HTML_BLOCK _) = Other "html"
|
||||
toCategory (HTML_INLINE _) = Other "html"
|
||||
toCategory (HEADING _) = Other "heading"
|
||||
toCategory (LIST (ListAttributes{..})) = Other $ case listType of
|
||||
BULLET_LIST -> "unordered list"
|
||||
ORDERED_LIST -> "ordered list"
|
||||
toCategory (LINK{}) = Other "link"
|
||||
toCategory (IMAGE{}) = Other "image"
|
||||
toCategory t = Other (show t)
|
||||
toSpan PosInfo{..} = SourceSpan "" (SourcePos (pred startLine) (pred startColumn)) (SourcePos (pred endLine) (pred endColumn))
|
||||
|
||||
-- | Return a parser based on the file extension (including the ".").
|
||||
parserForType :: Text -> Parser (Syntax Text) (Record '[Range, Category])
|
||||
parserForType mediaType = case languageForType mediaType of
|
||||
|
37
src/Language/Markdown.hs
Normal file
37
src/Language/Markdown.hs
Normal file
@ -0,0 +1,37 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
module Language.Markdown where
|
||||
|
||||
import CMark
|
||||
import Data.Record
|
||||
import Data.Text
|
||||
import Info
|
||||
import Parser
|
||||
import Prologue
|
||||
import Source
|
||||
import SourceSpan
|
||||
import Syntax
|
||||
|
||||
cmarkParser :: Parser (Syntax Text) (Record '[Range, Category])
|
||||
cmarkParser SourceBlob{..} = pure . toTerm (totalSpan source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source)
|
||||
where toTerm :: SourceSpan -> Node -> Cofree (Syntax Text) (Record '[Range, Category])
|
||||
toTerm within (Node position t children) = let span = maybe within toSpan position in cofree $ (sourceSpanToRange source span .: toCategory t .: RNil) :< case t of
|
||||
-- Leaves
|
||||
CODE text -> Leaf text
|
||||
TEXT text -> Leaf text
|
||||
CODE_BLOCK _ text -> Leaf text
|
||||
-- Branches
|
||||
_ -> Indexed (toTerm span <$> children)
|
||||
|
||||
toCategory :: NodeType -> Category
|
||||
toCategory (TEXT _) = Other "text"
|
||||
toCategory (CODE _) = Other "code"
|
||||
toCategory (HTML_BLOCK _) = Other "html"
|
||||
toCategory (HTML_INLINE _) = Other "html"
|
||||
toCategory (HEADING _) = Other "heading"
|
||||
toCategory (LIST (ListAttributes{..})) = Other $ case listType of
|
||||
BULLET_LIST -> "unordered list"
|
||||
ORDERED_LIST -> "ordered list"
|
||||
toCategory (LINK{}) = Other "link"
|
||||
toCategory (IMAGE{}) = Other "image"
|
||||
toCategory t = Other (show t)
|
||||
toSpan PosInfo{..} = SourceSpan "" (SourcePos (pred startLine) (pred startColumn)) (SourcePos (pred endLine) (pred endColumn))
|
Loading…
Reference in New Issue
Block a user