1
1
mirror of https://github.com/github/semantic.git synced 2024-12-22 06:11:49 +03:00

Revert "Source carries its Range."

This reverts commit 6e075787935c10b0bd7256673a5623cb5d1a4945.
This commit is contained in:
Rob Rix 2017-02-10 16:44:09 -05:00
parent f3bad55fee
commit 00c14e403a
3 changed files with 19 additions and 18 deletions

View File

@ -9,6 +9,7 @@ import Data.Record
import Diff
import Info
import Prologue
import Range
import qualified Data.List as List
import qualified Data.Map as Map hiding (null)
import Renderer
@ -151,9 +152,10 @@ termToDiffInfo source term = case unwrap term of
_ -> toLeafInfo term
where
toTermName' :: SyntaxTerm leaf fields -> Text
toTermName' subterm = toTermName (Source.slice (range subterm) source) subterm
toTermName' subterm = toTermName (Source.slice (subtermRange subterm) source) subterm
range = characterRange . extract
termToDiffInfo' subterm = termToDiffInfo (Source.slice (range subterm) source) subterm
subtermRange subterm = offsetRange (range subterm) (negate (start (range term)))
termToDiffInfo' subterm = termToDiffInfo (Source.slice (subtermRange subterm) source) subterm
toLeafInfo term = LeafInfo (category $ extract term) (toTermName' term) (getField $ extract term)
toTermName :: forall leaf fields. DefaultFields fields => Source -> SyntaxTerm leaf fields -> Text
@ -164,5 +166,6 @@ toTermName source term = case unwrap term of
_ -> toText source
where
toTermName' :: SyntaxTerm leaf fields -> Text
toTermName' subterm = toTermName (Source.slice (range subterm) source) subterm
toTermName' subterm = toTermName (Source.slice (range' subterm) source) subterm
range' subterm = offsetRange (range subterm) (negate (start (range term)))
range = characterRange . extract

View File

@ -1,3 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
module Source where
@ -13,7 +14,7 @@ data SourceBlob = SourceBlob { source :: Source, oid :: String, path :: FilePath
deriving (Show, Eq)
-- | The contents of a source file, represented as Text.
data Source = Source { sourceText :: Text, sourceRange :: Range }
newtype Source = Source { sourceText :: Text }
deriving (Eq, Show)
-- | The kind of a blob, along with it's file mode.
@ -45,18 +46,17 @@ idOrEmptySourceBlob blob = if isNothing (blobKind blob)
nullOid :: String
nullOid = "0000000000000000000000000000000000000000"
-- | Return a Source from a finite string.
-- | Return a Source from a list of items.
fromList :: [Char] -> Source
fromList = fromText . Text.pack
fromList = Source . Text.pack
-- | Return a Source of Chars from a Text.
fromText :: Text -> Source
fromText sourceText = Source sourceText sourceRange
where sourceRange = Range 0 (Text.length sourceText)
fromText = Source
-- | Return a Source that contains a slice of the given Source.
slice :: Range -> Source -> Source
slice range Source{..} = Source (Text.take (rangeLength range) (Text.drop (start range - start sourceRange) sourceText)) range
slice range = Source . Text.take (rangeLength range) . Text.drop (start range) . sourceText
-- | Return a String with the contents of the Source.
toString :: Source -> String
@ -72,13 +72,11 @@ at = Text.index . sourceText
-- | Remove the first item and return it with the rest of the source.
uncons :: Source -> Maybe (Char, Source)
uncons Source{..} = if Text.null sourceText then Nothing else Just (Text.head sourceText, Source (Text.tail sourceText) (snd (divideRange sourceRange (start sourceRange + 1))))
uncons (Source text) = if Text.null text then Nothing else Just (Text.head text, Source $ Text.tail text)
-- | Split the source into the longest prefix of elements that do not satisfy the predicate and the rest without copying.
break :: (Char -> Bool) -> Source -> (Source, Source)
break predicate Source{..} = (Source initial initialRange, Source remainder remainderRange)
where (initial, remainder) = Text.break predicate sourceText
(initialRange, remainderRange) = divideRange sourceRange (start sourceRange + Text.length initial)
break predicate (Source text) = let (start, remainder) = Text.break predicate text in (Source start, Source remainder)
-- | Split the contents of the source after newlines.
actualLines :: Source -> [Source]
@ -120,7 +118,7 @@ null :: Source -> Bool
null = Text.null . sourceText
instance Semigroup Source where
Source a ar <> Source b br = Source (a <> b) (ar <> br)
Source a <> Source b = Source (a <> b)
instance Monoid Source where
mempty = fromList []

View File

@ -48,24 +48,24 @@ documentToTerm language document SourceBlob{..} = alloca $ \ root -> do
name <- ts_node_p_name node document
name <- peekCString name
count <- ts_node_p_named_child_count node
children <- filter isNonEmpty <$> traverse (alloca . getChild ts_node_p_named_child node) (take (fromIntegral count) [0..])
children <- filter isNonEmpty <$> traverse (alloca . getChild ts_node_p_named_child (start range) node) (take (fromIntegral count) [0..])
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 { spanStart = startPos , spanEnd = endPos }
allChildrenCount <- ts_node_p_child_count node
let allChildren = filter isNonEmpty <$> traverse (alloca . getChild ts_node_p_child node) (take (fromIntegral allChildrenCount) [0..])
let allChildren = filter isNonEmpty <$> traverse (alloca . getChild ts_node_p_child (start range) node) (take (fromIntegral allChildrenCount) [0..])
-- Note: The strict application here is semantically important.
-- Without it, we may not evaluate the value until after weve exited
-- the scope that `node` was allocated within, meaning `alloca` will
-- free it & other stack data may overwrite it.
range `seq` sourceSpan `seq` assignTerm language source (range :. categoryForLanguageProductionName language (toS name) :. sourceSpan :. Nil) children allChildren
getChild getter node n out = do
getChild getter start node n out = do
_ <- getter node n out
let childRange = nodeRange node
toTerm out childRange (slice childRange source)
toTerm out childRange (slice (offsetRange childRange (negate start)) source)
{-# INLINE getChild #-}
isNonEmpty child = category (extract child) /= Empty