mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
Fixup remaining test cases.
This commit is contained in:
parent
d929a8c78a
commit
948deb489f
@ -80,7 +80,7 @@ instance CustomHasDeclaration whole Markdown.Heading where
|
||||
= Just $ HeadingDeclaration (headingText terms) mempty (locSpan ann) (blobLanguage blob) level
|
||||
where headingText terms = getSource $ maybe (locByteRange ann) sconcat (nonEmpty (headingByteRange <$> toList terms))
|
||||
headingByteRange (Term (In ann _), _) = locByteRange ann
|
||||
getSource = firstLine . toText . flip Source.slice blobSource
|
||||
getSource = firstLine . toText . Source.slice blobSource
|
||||
firstLine = T.takeWhile (/= '\n')
|
||||
|
||||
-- | Produce an 'ErrorDeclaration' for 'Syntax.Error' nodes.
|
||||
@ -126,11 +126,11 @@ getIdentifier finder Blob{..} (In a r)
|
||||
= let declRange = locByteRange a
|
||||
bodyRange = locByteRange <$> rewrite (fmap fst r) (finder >>^ annotation)
|
||||
-- Text-based gyrations to slice the identifier out of the provided blob source
|
||||
sliceFrom = T.stripEnd . toText . flip Source.slice blobSource . subtractRange declRange
|
||||
sliceFrom = T.stripEnd . toText . Source.slice blobSource . subtractRange declRange
|
||||
in maybe mempty sliceFrom bodyRange
|
||||
|
||||
getSource :: Source -> Loc -> Text
|
||||
getSource blobSource = toText . flip Source.slice blobSource . locByteRange
|
||||
getSource blobSource = toText . Source.slice blobSource . locByteRange
|
||||
|
||||
-- | Produce a 'Declaration' for 'Sum's using the 'HasDeclaration' instance & therefore using a 'CustomHasDeclaration' instance when one exists & the type is listed in 'DeclarationStrategy'.
|
||||
instance Apply (HasDeclaration' whole) fs => CustomHasDeclaration whole (Sum fs) where
|
||||
|
@ -99,7 +99,7 @@ instance (Enum symbol, Ord symbol, Show symbol) => Assigning symbol (Assignment
|
||||
leafNode s = Assignment NotNullable (IntSet.singleton (fromEnum s))
|
||||
[ (s, \ src state _ -> case stateInput state of
|
||||
[] -> Left (makeError (stateSpan state) [Right s] Nothing)
|
||||
s:_ -> case decodeUtf8' (sourceBytes (Source.slice (astRange s) src)) of
|
||||
s:_ -> case decodeUtf8' (sourceBytes (Source.slice src (astRange s))) of
|
||||
Left err -> Left (makeError (astSpan s) [Left "valid utf-8"] (Just (Left (show err))))
|
||||
Right text -> Right (advanceState state, text))
|
||||
]
|
||||
|
@ -15,7 +15,7 @@ import Prologue
|
||||
import Data.Blob
|
||||
import Data.Language
|
||||
import Semantic.IO
|
||||
import Data.Source
|
||||
import qualified Source.Source as Source
|
||||
import qualified Semantic.Git as Git
|
||||
import qualified Control.Concurrent.Async as Async
|
||||
import qualified Data.ByteString as B
|
||||
@ -25,7 +25,7 @@ readBlobFromFile :: forall m. MonadIO m => File -> m (Maybe Blob)
|
||||
readBlobFromFile (File "/dev/null" _) = pure Nothing
|
||||
readBlobFromFile (File path language) = do
|
||||
raw <- liftIO $ B.readFile path
|
||||
pure . Just . sourceBlob path language . fromUTF8 $ raw
|
||||
pure . Just . sourceBlob path language . Source.fromUTF8 $ raw
|
||||
|
||||
-- | Read a utf8-encoded file to a 'Blob', raising an IOError if it can't be found.
|
||||
readBlobFromFile' :: MonadIO m => File -> m Blob
|
||||
@ -51,7 +51,7 @@ readBlobsFromGitRepo path oid excludePaths includePaths = liftIO . fmap catMaybe
|
||||
, not (pathIsMinified path)
|
||||
, path `notElem` excludePaths
|
||||
, null includePaths || path `elem` includePaths
|
||||
= Just . sourceBlob' path lang oid . fromText <$> Git.catFile gitDir oid
|
||||
= Just . sourceBlob' path lang oid . Source.fromText <$> Git.catFile gitDir oid
|
||||
blobFromTreeEntry _ _ = pure Nothing
|
||||
|
||||
sourceBlob' filepath language (Git.OID oid) source = makeBlob source filepath language oid
|
||||
|
@ -51,7 +51,7 @@ contextualizing Blob{..} symbolsToSummarize = Streaming.mapMaybeM $ \case
|
||||
-> Just $ Tag iden x span (fmap fst xs) (firstLine (slice r)) (slice docsLiteralRange)
|
||||
_ -> Nothing
|
||||
where
|
||||
slice = fmap (stripEnd . Source.toText . flip Source.slice blobSource)
|
||||
slice = fmap (stripEnd . Source.toText . Source.slice blobSource)
|
||||
firstLine = fmap (T.take 180 . fst . breakOn "\n")
|
||||
|
||||
enterScope, exitScope :: ( Member (State [ContextToken]) sig
|
||||
|
@ -1,6 +1,7 @@
|
||||
module Data.Source.Spec (spec, testTree) where
|
||||
|
||||
import Data.Source
|
||||
import Source.Source (Source)
|
||||
import qualified Source.Source as Source
|
||||
import qualified Data.Text as Text
|
||||
import Source.Range
|
||||
import Source.Span
|
||||
@ -26,28 +27,28 @@ testTree = Tasty.testGroup "Data.Source"
|
||||
[ Tasty.testGroup "sourceLineRanges"
|
||||
[ prop "produces 1 more range than there are newlines" $ \ source -> do
|
||||
summarize source
|
||||
length (sourceLineRanges source) === length (Text.splitOn "\r\n" (toText source) >>= Text.splitOn "\r" >>= Text.splitOn "\n")
|
||||
length (Source.lineRanges source) === length (Text.splitOn "\r\n" (Source.toText source) >>= Text.splitOn "\r" >>= Text.splitOn "\n")
|
||||
|
||||
, prop "produces exhaustive ranges" $ \ source -> do
|
||||
summarize source
|
||||
foldMap (`slice` source) (sourceLineRanges source) === source
|
||||
foldMap (Source.slice source) (Source.lineRanges source) === source
|
||||
]
|
||||
|
||||
, Tasty.testGroup "totalSpan"
|
||||
[ testProperty "covers single lines" . property $ do
|
||||
n <- forAll $ Gen.int (Hedgehog.Range.linear 0 100)
|
||||
totalSpan (fromText (Text.replicate n "*")) === Span (Pos 1 1) (Pos 1 (max 1 (succ n)))
|
||||
Source.totalSpan (Source.fromText (Text.replicate n "*")) === Span (Pos 1 1) (Pos 1 (max 1 (succ n)))
|
||||
|
||||
, testProperty "covers multiple lines" . property $ do
|
||||
n <- forAll $ Gen.int (Hedgehog.Range.linear 0 100)
|
||||
totalSpan (fromText (Text.intersperse '\n' (Text.replicate n "*"))) === Span (Pos 1 1) (Pos (max 1 n) (if n > 0 then 2 else 1))
|
||||
Source.totalSpan (Source.fromText (Text.intersperse '\n' (Text.replicate n "*"))) === Span (Pos 1 1) (Pos (max 1 n) (if n > 0 then 2 else 1))
|
||||
]
|
||||
|
||||
]
|
||||
where summarize src = do
|
||||
let lines = sourceLines src
|
||||
let lines = Source.lines src
|
||||
-- FIXME: this should be using cover (reverted in 1b427b995), but that leads to flaky tests: hedgehog’s 'cover' implementation fails tests instead of warning, and currently has no equivalent to 'checkCoverage'.
|
||||
classify "empty" $ nullSource src
|
||||
classify "empty" $ Source.null src
|
||||
classify "single-line" $ length lines == 1
|
||||
classify "multiple lines" $ length lines > 1
|
||||
|
||||
@ -56,16 +57,16 @@ spec = do
|
||||
describe "newlineIndices" $ do
|
||||
it "finds \\n" $
|
||||
let source = "a\nb" in
|
||||
newlineIndices source `shouldBe` [1]
|
||||
Source.newlineIndices source `shouldBe` [1]
|
||||
it "finds \\r" $
|
||||
let source = "a\rb" in
|
||||
newlineIndices source `shouldBe` [1]
|
||||
Source.newlineIndices source `shouldBe` [1]
|
||||
it "finds \\r\\n" $
|
||||
let source = "a\r\nb" in
|
||||
newlineIndices source `shouldBe` [2]
|
||||
Source.newlineIndices source `shouldBe` [2]
|
||||
it "finds intermixed line endings" $
|
||||
let source = "hi\r}\r}\n xxx \r a" in
|
||||
newlineIndices source `shouldBe` [2, 4, 6, 12]
|
||||
Source.newlineIndices source `shouldBe` [2, 4, 6, 12]
|
||||
|
||||
insetSpan :: Span -> Span
|
||||
insetSpan sourceSpan = sourceSpan { spanStart = (spanStart sourceSpan) { posColumn = succ (posColumn (spanStart sourceSpan)) }
|
||||
|
@ -45,7 +45,7 @@ import Data.Functor.Listable as X
|
||||
import Data.Language as X
|
||||
import Data.List.NonEmpty as X (NonEmpty(..))
|
||||
import Data.Semilattice.Lower as X
|
||||
import Data.Source as X
|
||||
import Source.Source as X (Source)
|
||||
import Data.String
|
||||
import Data.Sum
|
||||
import Data.Term as X
|
||||
|
Loading…
Reference in New Issue
Block a user