1
1
mirror of https://github.com/github/semantic.git synced 2024-11-28 18:23:44 +03:00

Remove filepath from SourceSpan

This commit is contained in:
joshvera 2016-10-11 15:09:24 -04:00
parent c0ae593a06
commit 098655b1d9
5 changed files with 8 additions and 12 deletions

View File

@ -341,4 +341,4 @@ instance Arbitrary a => Arbitrary (DiffSummary a) where
instance P.Pretty DiffInfo where
pretty LeafInfo{..} = squotes (string $ toSL termName) <+> string (toSL categoryName)
pretty BranchInfo{..} = mconcat $ punctuate (string "," P.<> space) (pretty <$> branches)
pretty ErrorInfo{..} = squotes (string $ toSL termName) <+> "at" <+> (string . toSL $ displayStartEndPos errorSpan) <+> "in" <+> (string . toSL $ spanName errorSpan)
pretty ErrorInfo{..} = squotes (string $ toSL termName) <+> "at" <+> (string . toSL $ displayStartEndPos errorSpan)

View File

@ -82,8 +82,8 @@ lineByLineParser SourceBlob{..} = pure . cofree . root $ case foldl' annotateLea
(leaves, _) -> cofree <$> leaves
where
lines = actualLines source
root children = (Range 0 (length source) .: Program .: rangeToSourceSpan source (toS path) (Range 0 (length source)) .: RNil) :< Indexed children
leaf charIndex line = (Range charIndex (charIndex + T.length line) .: Program .: rangeToSourceSpan source (toS path) (Range charIndex (charIndex + T.length line)) .: RNil) :< Leaf line
root children = (Range 0 (length source) .: Program .: rangeToSourceSpan source (Range 0 (length source)) .: RNil) :< Indexed children
leaf charIndex line = (Range charIndex (charIndex + T.length line) .: Program .: rangeToSourceSpan source (Range charIndex (charIndex + T.length line)) .: RNil) :< Leaf line
annotateLeaves (accum, charIndex) line =
(accum <> [ leaf charIndex (toText line) ] , charIndex + length line)
toText = T.pack . Source.toString

View File

@ -12,7 +12,7 @@ import Source
import Syntax
cmarkParser :: Parser (Syntax Text) (Record '[Range, Category, SourceSpan])
cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) (rangeToSourceSpan source (toS path) $ totalRange source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source)
cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) (rangeToSourceSpan source $ totalRange source) $ commonmarkToNode [ optSourcePos, optSafe ] (toText source)
where toTerm :: Range -> SourceSpan -> Node -> Cofree (Syntax Text) (Record '[Range, Category, SourceSpan])
toTerm within withinSpan (Node position t children) =
let
@ -39,4 +39,4 @@ cmarkParser SourceBlob{..} = pure . toTerm (totalRange source) (rangeToSourceSpa
toCategory LINK{} = Other "link"
toCategory IMAGE{} = Other "image"
toCategory t = Other (show t)
toSpan PosInfo{..} = SourceSpan "" (SourcePos (pred startLine) (pred startColumn)) (SourcePos (pred endLine) endColumn)
toSpan PosInfo{..} = SourceSpan (SourcePos (pred startLine) (pred startColumn)) (SourcePos (pred endLine) endColumn)

View File

@ -99,8 +99,8 @@ sourceSpanToRange source SourceSpan{..} = Range start end
(leadingRanges, remainingRanges) = splitAt (line spanStart) (actualLineRanges (totalRange source) source)
sumLengths = sum . fmap (\ Range{..} -> end - start)
rangeToSourceSpan :: Source Char -> Text -> Range -> SourceSpan
rangeToSourceSpan source name range@Range{} = SourceSpan name startPos endPos
rangeToSourceSpan :: Source Char -> Range -> SourceSpan
rangeToSourceSpan source range@Range{} = SourceSpan startPos endPos
where startPos = maybe (SourcePos 1 1) (toStartPos 1) (head lineRanges)
endPos = toEndPos (length lineRanges) (last lineRanges)
lineRanges = actualLineRanges range source

View File

@ -45,11 +45,7 @@ documentToTerm language document SourceBlob{..} = alloca $ \ root -> do
let startPos = SourcePos (1 + (fromIntegral $! ts_node_p_start_point_row node)) (1 + (fromIntegral $! ts_node_p_start_point_column node))
let endPos = SourcePos (1 + (fromIntegral $! ts_node_p_end_point_row node)) (1 + (fromIntegral $! ts_node_p_end_point_column node))
let sourceSpan = SourceSpan {
spanName = toS path
, spanStart = startPos
, spanEnd = endPos
}
let sourceSpan = SourceSpan { spanStart = startPos , spanEnd = endPos }
-- Note: The strict application here is semantically important.
-- Without it, we may not evaluate the range until after weve exited