1
1
mirror of https://github.com/github/semantic.git synced 2024-12-26 16:33:03 +03:00

Use GeneralizedNewtypeDeriving to clean up Source.

O(1) null, and far fewer symbol collisions.
This commit is contained in:
Rob Rix 2016-03-11 18:31:01 -05:00
parent 59edb8ff41
commit 2c91333d16
6 changed files with 13 additions and 23 deletions

View File

@ -52,7 +52,7 @@ breakDownLeavesByWord source = cata replaceIn
where
replaceIn info@(Info range categories) (Leaf _) | ranges <- rangesAndWordsInSource range, length ranges > 1 = info :< Indexed (makeLeaf categories <$> ranges)
replaceIn info syntax = info :< syntax
rangesAndWordsInSource range = rangesAndWordsFrom (start range) (Source.toList $ slice range source)
rangesAndWordsInSource range = rangesAndWordsFrom (start range) (toString $ slice range source)
makeLeaf categories (range, substring) = Info range categories :< Leaf (T.pack substring)
-- | Transcode a file to a unicode source.

View File

@ -42,10 +42,10 @@ termConstructor :: (String -> Set.Set Category) -> Constructor
termConstructor mapping source range name = (Info range categories :<) . construct
where
categories = mapping name
construct [] = Leaf . pack . toList $ slice range source
construct [] = Leaf . pack . toString $ slice range source
construct children | isFixed categories = Fixed children
construct children | isKeyed categories = Keyed . Map.fromList $ assignKey <$> children
construct children = Indexed children
assignKey node@(Info _ categories :< Fixed (key : _)) | Set.member Pair categories = (getSubstring key, node)
assignKey node = (getSubstring node, node)
getSubstring (Info range _ :< _) = pack . toList $ slice range source
getSubstring (Info range _ :< _) = pack . toString $ slice range source

View File

@ -20,7 +20,7 @@ import Diff
import Line
import Range
import Renderer
import Source hiding (fromList, toList)
import Source hiding (fromList)
import SplitDiff
import Syntax
import Term

View File

@ -102,7 +102,7 @@ header blobs hunk = intercalate "\n" [filepathHeader, fileModeHeader, beforeFile
-- | Render a diff as a series of hunks.
hunks :: Renderer a [Hunk (SplitDiff a Info)]
hunks _ blobs | Both (True, True) <- Source.null . source <$> blobs = [Hunk { offset = mempty, changes = [], trailingContext = [] }]
hunks _ blobs | Both (True, True) <- null . source <$> blobs = [Hunk { offset = mempty, changes = [], trailingContext = [] }]
hunks diff blobs = hunksInRows (Both (1, 1)) $ fmap (fmap Prelude.fst) <$> splitDiffByLines (source <$> blobs) diff
-- | Given beginning line numbers, turn rows in a split diff into hunks in a

View File

@ -1,10 +1,12 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Source where
import Range
import qualified Data.Vector as Vector
import Data.Foldable
import qualified Data.Text as T
import qualified Data.Vector as Vector
import Data.Word
import Numeric
import Range
data SourceKind = PlainBlob Word32 | ExecutableBlob Word32 | SymlinkBlob Word32
deriving (Show, Eq)
@ -23,7 +25,7 @@ defaultPlainBlob = PlainBlob 0o100644
-- | The contents of a source file, backed by a vector for efficient slicing.
newtype Source a = Source { getVector :: Vector.Vector a }
deriving (Eq, Show, Functor, Traversable)
deriving (Eq, Show, Foldable, Functor, Traversable)
-- | Return a Source from a list of items.
fromList :: [a] -> Source a
@ -33,10 +35,6 @@ fromList = Source . Vector.fromList
fromText :: T.Text -> Source Char
fromText = Source . Vector.fromList . T.unpack
-- | Return a list of items with the contents of the Source.
toList :: Source a -> [a]
toList = Vector.toList . getVector
-- | Return a Source that contains a slice of the given Source.
slice :: Range -> Source a -> Source a
slice range = Source . Vector.slice (start range) (rangeLength range) . getVector
@ -49,17 +47,13 @@ toString = toList
at :: Source a -> Int -> a
at = (Vector.!) . getVector
-- | Test whether the source is empty.
null :: Source a -> Bool
null = Vector.null . getVector
-- | Prepend an item.
cons :: a -> Source a -> Source a
cons a = Source . Vector.cons a . getVector
-- | Remove the first item and return it with the rest of the source.
uncons :: Source a -> Maybe (a, Source a)
uncons (Source vector) = if Vector.null vector then Nothing else Just (Vector.head vector, Source $ Vector.tail vector)
uncons (Source vector) = if null vector then Nothing else Just (Vector.head vector, Source $ Vector.tail vector)
-- | Split the source into the longest prefix of elements that do not satisfy the predicate and the rest without copying.
break :: (a -> Bool) -> Source a -> (Source a, Source a)
@ -71,7 +65,7 @@ break predicate (Source vector) = let (start, remainder) = Vector.break predicat
-- | Split the contents of the source after newlines.
actualLines :: Source Char -> [Source Char]
actualLines source | Source.null source = [ source ]
actualLines source | null source = [ source ]
actualLines source = case Source.break (== '\n') source of
(l, lines') -> case uncons lines' of
Nothing -> [ l ]
@ -81,7 +75,3 @@ actualLines source = case Source.break (== '\n') source of
actualLineRanges :: Range -> Source Char -> [Range]
actualLineRanges range = drop 1 . scanl toRange (Range (start range) (start range)) . actualLines . slice range
where toRange previous string = Range (end previous) $ end previous + length string
instance Foldable Source where
foldMap f = foldMap f . getVector
length = Vector.length . getVector

View File

@ -16,7 +16,7 @@ treeSitterParser :: Language -> Ptr TS.Language -> Parser
treeSitterParser language grammar contents = do
document <- ts_document_make
ts_document_set_language document grammar
withCString (toList contents) (\source -> do
withCString (toString contents) (\source -> do
ts_document_set_input_string document source
ts_document_parse document
term <- documentToTerm (termConstructor $ categoriesForLanguage language) document contents