mirror of
https://github.com/github/semantic.git
synced 2024-12-29 18:06:14 +03:00
fewer spurious changes
This commit is contained in:
parent
a8212b14a3
commit
16066c1f7d
@ -1,9 +1,6 @@
|
||||
{-# LANGUAGE MultiWayIf #-}
|
||||
|
||||
module Data.Project where
|
||||
|
||||
import Data.ByteString.Char8 as BC (pack, writeFile)
|
||||
import Data.Blob
|
||||
import Data.ByteString.Char8 as BC (pack)
|
||||
import Data.Language
|
||||
import Prologue
|
||||
import System.FilePath.Posix
|
||||
@ -33,6 +30,3 @@ data File = File
|
||||
file :: FilePath -> File
|
||||
file path = File path (languageForFilePath path)
|
||||
where languageForFilePath = languageForType . takeExtension
|
||||
|
||||
blobToFile :: Blob -> File
|
||||
blobToFile (Blob _ f l) = File f l
|
||||
|
@ -138,6 +138,7 @@ someParser Python = SomeParser pythonParser
|
||||
someParser Ruby = SomeParser rubyParser
|
||||
someParser TypeScript = SomeParser typescriptParser
|
||||
someParser PHP = SomeParser phpParser
|
||||
someParser Unknown = error "No parser suitable for an unknown language."
|
||||
|
||||
|
||||
goParser :: Parser Go.Term
|
||||
|
@ -9,6 +9,7 @@ import Analysis.Declaration
|
||||
import Analysis.PackageDef
|
||||
import Data.Aeson
|
||||
import Data.Blob
|
||||
import Data.Language (ensureLanguage)
|
||||
import Data.Record
|
||||
import Data.Span
|
||||
import Data.Term
|
||||
@ -44,7 +45,7 @@ renderToImports blob term = ImportSummary $ toMap (termToModule blob term)
|
||||
_ -> defaultModuleName
|
||||
|
||||
makeModule :: (HasField fields Span, HasField fields (Maybe Declaration)) => T.Text -> Blob -> [Record fields] -> Module
|
||||
makeModule name Blob{..} ds = Module name [T.pack blobPath] (T.pack (show blobLanguage)) (mapMaybe importSummary ds) (mapMaybe (declarationSummary name) ds) (mapMaybe referenceSummary ds)
|
||||
makeModule name Blob{..} ds = Module name [T.pack blobPath] (T.pack . show <$> ensureLanguage blobLanguage) (mapMaybe importSummary ds) (mapMaybe (declarationSummary name) ds) (mapMaybe referenceSummary ds)
|
||||
|
||||
|
||||
getPackageDef :: HasField fields (Maybe PackageDef) => Record fields -> Maybe PackageDef
|
||||
@ -79,7 +80,7 @@ referenceSummary record = case getDeclaration record of
|
||||
data Module = Module
|
||||
{ moduleName :: T.Text
|
||||
, modulePaths :: [T.Text]
|
||||
, moduleLanguage :: T.Text
|
||||
, moduleLanguage :: Maybe T.Text
|
||||
, moduleImports :: [ImportStatement]
|
||||
, moduleDeclarations :: [SymbolDeclaration]
|
||||
, moduleCalls :: [CallExpression]
|
||||
|
@ -10,6 +10,7 @@ import Prologue
|
||||
import Analysis.Declaration
|
||||
import Data.Aeson
|
||||
import Data.Blob
|
||||
import Data.Language (ensureLanguage)
|
||||
import Data.Record
|
||||
import Data.Span
|
||||
import Data.Term
|
||||
@ -43,7 +44,7 @@ symbolSummary SymbolFields{..} path _ record = case getDeclaration record of
|
||||
Just declaration -> Just Symbol
|
||||
{ symbolName = when symbolFieldsName (declarationIdentifier declaration)
|
||||
, symbolPath = when symbolFieldsPath (T.pack path)
|
||||
, symbolLang = when symbolFieldsLang (T.pack (show (declarationLanguage declaration)))
|
||||
, symbolLang = join (when symbolFieldsLang (T.pack . show <$> ensureLanguage (declarationLanguage declaration)))
|
||||
, symbolKind = when symbolFieldsKind (toCategoryName declaration)
|
||||
, symbolLine = when symbolFieldsLine (declarationText declaration)
|
||||
, symbolSpan = when symbolFieldsSpan (getField record)
|
||||
|
Loading…
Reference in New Issue
Block a user