1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 08:54:07 +03:00

Merge pull request #327 from github/remove-info-line-range

Remove line range from Info
This commit is contained in:
Rob Rix 2015-12-14 17:20:12 -05:00
commit 86cf5df9e7
6 changed files with 25 additions and 35 deletions

View File

@ -30,10 +30,10 @@ data TSNode = TsNode { _data :: Ptr (), offset :: TSLength }
deriving (Show, Eq)
instance Storable TSNode where
alignment n = 24
sizeOf n = 24
peek p = error "Haskell code should never read TSNode values directly."
poke p n = error "Haskell code should never write TSNode values directly."
alignment _ = 24
sizeOf _ = 24
peek _ = error "Haskell code should never read TSNode values directly."
poke _ _ = error "Haskell code should never write TSNode values directly."
foreign import ccall "app/bridge.h ts_document_root_node_p" ts_document_root_node_p :: Ptr TSDocument -> Ptr TSNode -> IO ()
foreign import ccall "app/bridge.h ts_node_p_name" ts_node_p_name :: Ptr TSNode -> Ptr TSDocument -> IO CString
@ -41,8 +41,6 @@ foreign import ccall "app/bridge.h ts_node_p_named_child_count" ts_node_p_named_
foreign import ccall "app/bridge.h ts_node_p_named_child" ts_node_p_named_child :: Ptr TSNode -> CSize -> Ptr TSNode -> IO CSize
foreign import ccall "app/bridge.h ts_node_p_pos_chars" ts_node_p_pos_chars :: Ptr TSNode -> IO CSize
foreign import ccall "app/bridge.h ts_node_p_size_chars" ts_node_p_size_chars :: Ptr TSNode -> IO CSize
foreign import ccall "app/bridge.h ts_node_p_start_point" ts_node_p_start_point :: Ptr TSNode -> IO CSize
foreign import ccall "app/bridge.h ts_node_p_end_point" ts_node_p_end_point :: Ptr TSNode -> IO CSize
keyedProductions :: Set String
keyedProductions = fromList [ "object" ]
@ -71,8 +69,7 @@ documentToTerm document contents = alloca $ \root -> do
name <- peekCString name
children <- withNamedChildren node toTerm
range <- range node
lineRange <- getLineRange node
annotation <- return . Info range lineRange $ singleton name
annotation <- return . Info range $ singleton name
return (name, annotation :< case children of
[] -> Leaf $ substring range contents
_ | member name keyedProductions -> Keyed $ Map.fromList children
@ -86,7 +83,7 @@ withNamedChildren node transformNode = do
then return []
else mapM (alloca . getChild) [0..pred count] where
getChild n out = do
ts_node_p_named_child node n out
_ <- ts_node_p_named_child node n out
transformNode out
range :: Ptr TSNode -> IO Range
@ -96,9 +93,3 @@ range node = do
let start = fromIntegral pos
end = start + fromIntegral size
return Range { start = start, end = end }
getLineRange :: Ptr TSNode -> IO Range
getLineRange node = do
startLine <- ts_node_p_start_point node
endLine <- ts_node_p_end_point node
return Range { start = fromIntegral startLine, end = fromIntegral endLine }

View File

@ -13,7 +13,7 @@ data Annotated a annotation f = Annotated annotation (Syntax a f)
type Category = String
data Info = Info { characterRange :: Range, lineRange :: Range, categories :: (Set Category) }
data Info = Info { characterRange :: Range, categories :: (Set Category) }
deriving (Eq, Show)
instance Categorizable Info where

View File

@ -10,13 +10,12 @@ import qualified Data.Set as Set
type Parser = String -> IO (Term String Info)
lineByLineParser :: Parser
lineByLineParser input = return . root . Indexed $ case foldl annotateLeaves ([], 0, 0) lines of
(leaves, _, _) -> leaves
lineByLineParser input = return . root . Indexed $ case foldl annotateLeaves ([], 0) lines of
(leaves, _) -> leaves
where
lines = Prelude.lines input
root syntax = Info (Range 0 $ length input) (Range 0 $ length lines) Set.empty :< syntax
leaf charIndex lineIndex line = Info (Range charIndex $ charIndex + length line) (Range lineIndex $ lineIndex + 1) Set.empty :< Leaf line
annotateLeaves (accum, charIndex, lineIndex) line =
(accum ++ [ leaf charIndex lineIndex line ]
, charIndex + length line + 1
, lineIndex + 1)
root syntax = Info (Range 0 $ length input) Set.empty :< syntax
leaf charIndex line = Info (Range charIndex $ charIndex + length line) Set.empty :< Leaf line
annotateLeaves (accum, charIndex) line =
(accum ++ [ leaf charIndex line ]
, charIndex + length line + 1)

View File

@ -152,7 +152,7 @@ diffToRows (Pure (Replace a b)) _ before after = (replacedRows, (leftRange, righ
-- | Takes a term and a `source` and returns a list of HTML lines
-- | and their range within `source`.
termToLines :: Term a Info -> String -> ([Line], Range)
termToLines (Info range _ categories :< syntax) source = (rows syntax, range)
termToLines (Info range categories :< syntax) source = (rows syntax, range)
where
rows (Leaf _) = reverse $ foldl adjoin2Lines [] $ Line . (:[]) <$> elements
rows (Indexed i) = rewrapLineContentsInUl <$> childLines i
@ -173,7 +173,7 @@ termToLines (Info range _ categories :< syntax) source = (rows syntax, range)
-- | Given an Annotated and before/after strings, returns a list of `Row`s representing the newline-separated diff.
annotatedToRows :: Annotated a (Info, Info) (Diff a Info) -> String -> String -> ([Row], (Range, Range))
annotatedToRows (Annotated (Info left _ leftCategories, Info right _ rightCategories) syntax) before after = (rows syntax, ranges)
annotatedToRows (Annotated (Info left leftCategories, Info right rightCategories) syntax) before after = (rows syntax, ranges)
where
rows (Leaf _) = zipWithMaybe rowFromMaybeRows leftElements rightElements
rows (Indexed i) = wrapRows i

View File

@ -18,10 +18,10 @@ unified diff before after = do
return . mconcat . chunksToByteStrings renderer . fst $ iter g mapped where
mapped = fmap (unifiedPatch &&& range) diff
g (Annotated (_, info) syntax) = annotationAndSyntaxToChunks after info syntax
annotationAndSyntaxToChunks source (Info range _ _) (Leaf _) = (pure . chunk $ substring range source, Just range)
annotationAndSyntaxToChunks source (Info range _ _) (Indexed i) = (unifiedRange range i source, Just range)
annotationAndSyntaxToChunks source (Info range _ _) (Fixed f) = (unifiedRange range f source, Just range)
annotationAndSyntaxToChunks source (Info range _ _) (Keyed k) = (unifiedRange range (sort $ snd <$> Map.toList k) source, Just range)
annotationAndSyntaxToChunks source (Info range _) (Leaf _) = (pure . chunk $ substring range source, Just range)
annotationAndSyntaxToChunks source (Info range _) (Indexed i) = (unifiedRange range i source, Just range)
annotationAndSyntaxToChunks source (Info range _) (Fixed f) = (unifiedRange range f source, Just range)
annotationAndSyntaxToChunks source (Info range _) (Keyed k) = (unifiedRange range (sort $ snd <$> Map.toList k) source, Just range)
unifiedPatch :: Patch (Term a Info) -> [Chunk String]
unifiedPatch patch = (fore red . bold <$> beforeChunk) <> (fore green . bold <$> afterChunk) where
@ -40,7 +40,7 @@ unified diff before after = do
range :: Patch (Term a Info) -> Maybe Range
range patch = range . extract <$> after patch where
extract (annotation :< _) = annotation
range (Info range _ _) = range
range (Info range _) = range
change :: String -> [Chunk String] -> [Chunk String]
change bound content = [ chunk "{", chunk bound ] ++ content ++ [ chunk bound, chunk "}" ]

View File

@ -149,7 +149,7 @@ main = hspec $ do
it "should split multi-line deletions across multiple rows" $
let (sourceA, sourceB) = ("/*\n*/\na", "a") in
annotatedToRows (formatted sourceA sourceB "branch" (Indexed [
Pure . Delete $ (Info (Range 0 5) (Range 0 2) (Set.fromList ["leaf"]) :< (Leaf "")),
Pure . Delete $ (Info (Range 0 5) (Set.fromList ["leaf"]) :< (Leaf "")),
Free . offsetAnnotated 6 0 $ unchanged "a" "leaf" (Leaf "")
])) sourceA sourceB `shouldBe`
([
@ -190,7 +190,7 @@ main = hspec $ do
describe "termToLines" $ do
it "splits multi-line terms into multiple lines" $
termToLines (Info (Range 0 5) (Range 0 2) (Set.singleton "leaf") :< (Leaf "")) "/*\n*/"
termToLines (Info (Range 0 5) (Set.singleton "leaf") :< (Leaf "")) "/*\n*/"
`shouldBe`
([
Line [ span "/*", Break ],
@ -216,9 +216,9 @@ main = hspec $ do
leftRowText text = leftRow [ Text text ]
leftRow xs = Row (Line xs) EmptyLine
rowText a b = Row (Line [ Text a ]) (Line [ Text b ])
info source category = Info (totalRange source) (Range 0 0) (Set.fromList [ category ])
info source category = Info (totalRange source) (Set.fromList [ category ])
unchanged source category = formatted source source category
formatted source1 source2 category = Annotated (info source1 category, info source2 category)
offsetInfo by (Info (Range start end) lineRange categories) = Info (Range (start + by) (end + by)) lineRange categories
offsetInfo by (Info (Range start end) categories) = Info (Range (start + by) (end + by)) categories
offsetAnnotated by1 by2 (Annotated (left, right) syntax) = Annotated (offsetInfo by1 left, offsetInfo by2 right) syntax
span = Span (Just "category-leaf")