mirror of
https://github.com/github/semantic.git
synced 2024-11-24 00:42:33 +03:00
legacyMakeBlob => makeBlob. Also unpack File.
This commit is contained in:
parent
63a7f117eb
commit
8e0962712e
@ -6,7 +6,7 @@ module Data.Blob
|
||||
, Blobs(..)
|
||||
, blobLanguage
|
||||
, blobPath
|
||||
, legacyMakeBlob
|
||||
, makeBlob
|
||||
, decodeBlobs
|
||||
, nullBlob
|
||||
, sourceBlob
|
||||
@ -34,9 +34,10 @@ import Data.Language
|
||||
import Data.Source as Source
|
||||
|
||||
-- | A 'FilePath' paired with its corresponding 'Language'.
|
||||
-- Unpacked to have the same size overhead as (FilePath, Language).
|
||||
data File = File
|
||||
{ filePath :: FilePath
|
||||
, fileLanguage :: Language
|
||||
{ filePath :: {-# UNPACK #-} !FilePath
|
||||
, fileLanguage :: {-# UNPACK #-} !Language
|
||||
} deriving (Show, Eq, Generic)
|
||||
|
||||
fileForPath :: FilePath -> File
|
||||
@ -55,8 +56,9 @@ blobLanguage = fileLanguage . blobFile
|
||||
blobPath :: Blob -> FilePath
|
||||
blobPath = filePath . blobFile
|
||||
|
||||
legacyMakeBlob :: Source -> FilePath -> Language -> Text -> Blob
|
||||
legacyMakeBlob s p l = Blob s (File p l)
|
||||
makeBlob :: Source -> FilePath -> Language -> Text -> Blob
|
||||
makeBlob s p l = Blob s (File p l)
|
||||
{-# INLINE makeBlob #-}
|
||||
|
||||
newtype Blobs a = Blobs { blobs :: [a] }
|
||||
deriving (Generic, FromJSON)
|
||||
@ -71,12 +73,12 @@ nullBlob :: Blob -> Bool
|
||||
nullBlob Blob{..} = nullSource blobSource
|
||||
|
||||
sourceBlob :: FilePath -> Language -> Source -> Blob
|
||||
sourceBlob filepath language source = legacyMakeBlob source filepath language mempty
|
||||
sourceBlob filepath language source = makeBlob source filepath language mempty
|
||||
|
||||
inferringLanguage :: Source -> FilePath -> Language -> Blob
|
||||
inferringLanguage src pth lang
|
||||
| knownLanguage lang = legacyMakeBlob src pth lang mempty
|
||||
| otherwise = legacyMakeBlob src pth (languageForFilePath pth) mempty
|
||||
| knownLanguage lang = makeBlob src pth lang mempty
|
||||
| otherwise = makeBlob src pth (languageForFilePath pth) mempty
|
||||
|
||||
decodeBlobs :: BL.ByteString -> Either String [Blob]
|
||||
decodeBlobs = fmap blobs <$> eitherDecode
|
||||
|
@ -53,7 +53,7 @@ readBlobsFromGitRepo path oid excludePaths = liftIO . fmap catMaybes $
|
||||
= Just . sourceBlob' path lang oid . fromText <$> Git.catFile gitDir oid
|
||||
blobFromTreeEntry _ _ = pure Nothing
|
||||
|
||||
sourceBlob' filepath language (Git.OID oid) source = legacyMakeBlob source filepath language oid
|
||||
sourceBlob' filepath language (Git.OID oid) source = makeBlob source filepath language oid
|
||||
|
||||
readFilePair :: MonadIO m => File -> File -> m BlobPair
|
||||
readFilePair a b = do
|
||||
|
@ -98,7 +98,7 @@ instance APIBridge T.Text Data.Language where
|
||||
instance APIBridge API.Blob Data.Blob where
|
||||
bridging = iso apiBlobToBlob blobToApiBlob where
|
||||
blobToApiBlob b = API.Blob (toText (Data.blobSource b)) (T.pack (Data.blobPath b)) (bridging # Data.blobLanguage b)
|
||||
apiBlobToBlob API.Blob{..} = Data.legacyMakeBlob (fromText content) (T.unpack path) (language ^. bridging) mempty
|
||||
apiBlobToBlob API.Blob{..} = Data.makeBlob (fromText content) (T.unpack path) (language ^. bridging) mempty
|
||||
|
||||
|
||||
instance APIConvert API.BlobPair Data.BlobPair where
|
||||
|
@ -568,7 +568,7 @@ instance Listable Span where
|
||||
tiers = cons2 Span
|
||||
|
||||
instance Listable Blob where
|
||||
tiers = cons4 legacyMakeBlob
|
||||
tiers = cons4 makeBlob
|
||||
|
||||
instance Listable BlobPair where
|
||||
tiers = liftTiers tiers
|
||||
|
@ -67,5 +67,5 @@ spec = describe "reprinting" $ do
|
||||
it "should be able to parse the output of a refactor" $ do
|
||||
let (Just tagged) = rewrite (mark Unmodified tree) (topDownAny increaseNumbers)
|
||||
let (Right printed) = runReprinter src defaultJSONPipeline tagged
|
||||
tree' <- runTaskOrDie (parse jsonParser (legacyMakeBlob printed path Language.JSON mempty))
|
||||
tree' <- runTaskOrDie (parse jsonParser (makeBlob printed path Language.JSON mempty))
|
||||
length tree' `shouldSatisfy` (/= 0)
|
||||
|
@ -25,4 +25,4 @@ spec = parallel $ do
|
||||
output <- fmap runBuilder . runTaskOrDie $ parseTermBuilder TermSExpression [methodsBlob]
|
||||
output `shouldBe` "(Statements\n (Method\n (Empty)\n (Identifier)\n (Statements)))\n"
|
||||
where
|
||||
methodsBlob = legacyMakeBlob "def foo\nend\n" "methods.rb" Ruby mempty
|
||||
methodsBlob = makeBlob "def foo\nend\n" "methods.rb" Ruby mempty
|
||||
|
Loading…
Reference in New Issue
Block a user