mirror of
https://github.com/github/semantic.git
synced 2024-11-26 09:07:39 +03:00
Revert to master for semantic-source
This commit is contained in:
parent
d3a825f7e1
commit
56f04f1c2d
@ -28,14 +28,11 @@ module Source.Source
|
||||
, lineRanges
|
||||
, lineRangesWithin
|
||||
, newlineIndices
|
||||
, takeLine
|
||||
, lineRange
|
||||
) where
|
||||
|
||||
import Prelude hiding (drop, take)
|
||||
|
||||
import Control.Arrow ((&&&))
|
||||
import Control.Applicative
|
||||
import Control.DeepSeq (NFData)
|
||||
import Data.Aeson (FromJSON (..), withText)
|
||||
import qualified Data.ByteString as B
|
||||
@ -146,19 +143,3 @@ newlineIndices = go 0 where
|
||||
searchLF = B.elemIndex (toEnum (ord '\n'))
|
||||
searchCR = B.elemIndex (toEnum (ord '\r'))
|
||||
{-# INLINE newlineIndices #-}
|
||||
|
||||
takeLine :: Source -> Range -> Source
|
||||
takeLine src = slice src . lineRange src
|
||||
|
||||
lineRange :: Source -> Range -> Range
|
||||
lineRange src (Range start end) = Range lineStart lineEnd
|
||||
where
|
||||
lineStart = maybe start (start -) $ B.elemIndex lfChar precedingSource <|> B.elemIndex crChar precedingSource
|
||||
precedingSource = B.reverse $ bytes (Source.Source.slice src (Range 0 start))
|
||||
|
||||
lineEnd = maybe end (start +) $ B.elemIndex crChar remainingSource <|> B.elemIndex lfChar remainingSource
|
||||
remainingSource = bytes $ Source.Source.slice src (Range start eof)
|
||||
|
||||
lfChar = toEnum (ord '\n')
|
||||
crChar = toEnum (ord '\r')
|
||||
eof = Source.Source.length src
|
||||
|
@ -8,7 +8,6 @@ import Hedgehog hiding (Range)
|
||||
import qualified Hedgehog.Gen as Gen
|
||||
import qualified Hedgehog.Range as Range
|
||||
import qualified Source.Source as Source
|
||||
import qualified Source.Range as Source
|
||||
import Source.Span
|
||||
import qualified Test.Tasty as Tasty
|
||||
import Test.Tasty.HUnit
|
||||
@ -50,16 +49,6 @@ testTree = Tasty.testGroup "Data.Source"
|
||||
, testCase "finds \\r\\n" $ Source.newlineIndices "a\r\nb" @?= [2]
|
||||
, testCase "finds intermixed line endings" $ Source.newlineIndices "hi\r}\r}\n xxx \r a" @?= [2, 4, 6, 12]
|
||||
]
|
||||
|
||||
, Tasty.testGroup "takeLine"
|
||||
[ testCase "blank" $ Source.takeLine (Source.fromText "") (Source.Range 0 0) @?= (Source.fromText "")
|
||||
, testCase "newline" $ Source.takeLine (Source.fromText "\n") (Source.Range 0 0) @?= (Source.fromText "")
|
||||
, testCase "newline full range" $ Source.takeLine (Source.fromText "\n") (Source.Range 0 1) @?= (Source.fromText "")
|
||||
, testCase "ascii lf" $ Source.takeLine (Source.fromText "hi\n a\nb\n") (Source.Range 5 6) @?= (Source.fromText " a")
|
||||
, testCase "ascii crlf" $ Source.takeLine (Source.fromText "hi\r\n a\r\nb\r\n") (Source.Range 5 6) @?= (Source.fromText " a")
|
||||
, testCase "unicode" $ Source.takeLine (Source.fromText "hi\n à.a\nb\n") (Source.Range 8 9) @?= (Source.fromText " à.a")
|
||||
, testCase "extended unicode" $ Source.takeLine (Source.fromText "hi\n 😀.a\nb\n") (Source.Range 10 11) @?= (Source.fromText " 😀.a")
|
||||
]
|
||||
]
|
||||
|
||||
summarize :: Source.Source -> PropertyT IO ()
|
||||
|
Loading…
Reference in New Issue
Block a user