mirror of
https://github.com/github/semantic.git
synced 2024-12-26 00:12:29 +03:00
Disable import-graph specs for now
This commit is contained in:
parent
55cd6e4549
commit
208d16e131
@ -240,7 +240,6 @@ test-suite test
|
|||||||
, Diffing.Interpreter.Spec
|
, Diffing.Interpreter.Spec
|
||||||
, Integration.Spec
|
, Integration.Spec
|
||||||
, Matching.Go.Spec
|
, Matching.Go.Spec
|
||||||
, Rendering.Imports.Spec
|
|
||||||
, Rendering.TOC.Spec
|
, Rendering.TOC.Spec
|
||||||
, Semantic.Spec
|
, Semantic.Spec
|
||||||
, Semantic.CLI.Spec
|
, Semantic.CLI.Spec
|
||||||
|
@ -18,7 +18,6 @@ import qualified Data.Syntax as Syntax
|
|||||||
import qualified Data.Syntax.Declaration as Declaration
|
import qualified Data.Syntax.Declaration as Declaration
|
||||||
import qualified Data.Syntax.Expression as Expression
|
import qualified Data.Syntax.Expression as Expression
|
||||||
import qualified Language.Ruby.Syntax as Ruby.Syntax
|
import qualified Language.Ruby.Syntax as Ruby.Syntax
|
||||||
import qualified Language.Go.Syntax as Go.Syntax
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.Encoding as T
|
import qualified Data.Text.Encoding as T
|
||||||
import qualified Language.Markdown.Syntax as Markdown
|
import qualified Language.Markdown.Syntax as Markdown
|
||||||
@ -123,40 +122,9 @@ instance CustomHasDeclaration whole Ruby.Syntax.Class where
|
|||||||
customToDeclaration blob@Blob{..} ann decl@(Ruby.Syntax.Class (Term (In identifierAnn _), _) _ _)
|
customToDeclaration blob@Blob{..} ann decl@(Ruby.Syntax.Class (Term (In identifierAnn _), _) _ _)
|
||||||
= Just $ ClassDeclaration (getSource blobSource identifierAnn) (getRubyClassSource blob (In ann decl)) blobLanguage
|
= Just $ ClassDeclaration (getSource blobSource identifierAnn) (getRubyClassSource blob (In ann decl)) blobLanguage
|
||||||
|
|
||||||
-- instance CustomHasDeclaration (Union fs) Declaration.Import where
|
|
||||||
-- customToDeclaration Blob{..} _ (Declaration.Import (Term (In fromAnn _), _) symbols _)
|
|
||||||
-- = Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromAnn) "" (fmap getSymbol symbols) blobLanguage
|
|
||||||
-- where
|
|
||||||
-- getSymbol = let f = (T.decodeUtf8 . friendlyName) in bimap f f
|
|
||||||
|
|
||||||
-- instance (Syntax.Identifier :< fs) => CustomHasDeclaration (Union fs) Declaration.QualifiedImport where
|
|
||||||
-- customToDeclaration Blob{..} _ (Declaration.QualifiedImport (Term (In fromAnn _), _) (Term (In aliasAnn aliasF), _) symbols)
|
|
||||||
-- | Just (Syntax.Identifier alias) <- prj aliasF = Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromAnn) (toName alias) (fmap getSymbol symbols) blobLanguage
|
|
||||||
-- | otherwise = Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromAnn) (getSource blobSource aliasAnn) (fmap getSymbol symbols) blobLanguage
|
|
||||||
-- where
|
|
||||||
-- getSymbol = bimap toName toName
|
|
||||||
-- toName = T.decodeUtf8 . friendlyName
|
|
||||||
|
|
||||||
instance CustomHasDeclaration (Union fs) Go.Syntax.SideEffectImport where
|
|
||||||
customToDeclaration Blob{..} _ (Go.Syntax.SideEffectImport (Go.Syntax.ImportPath path) _)
|
|
||||||
= Just $ ImportDeclaration (T.pack path) "" [] blobLanguage
|
|
||||||
|
|
||||||
instance CustomHasDeclaration (Union fs) Ruby.Syntax.Require where
|
|
||||||
customToDeclaration Blob{..} _ (Ruby.Syntax.Require _ (Term (In fromAnn _), _))
|
|
||||||
= Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromAnn) "" [] blobLanguage
|
|
||||||
|
|
||||||
instance CustomHasDeclaration (Union fs) Ruby.Syntax.Load where
|
|
||||||
customToDeclaration Blob{..} _ (Ruby.Syntax.Load ((Term (In fromArgs _), _):_))
|
|
||||||
= Just $ ImportDeclaration ((stripQuotes . getSource blobSource) fromArgs) "" [] blobLanguage
|
|
||||||
customToDeclaration Blob{..} _ (Ruby.Syntax.Load _)
|
|
||||||
= Nothing
|
|
||||||
|
|
||||||
getSource :: HasField fields Range => Source -> Record fields -> Text
|
getSource :: HasField fields Range => Source -> Record fields -> Text
|
||||||
getSource blobSource = toText . flip Source.slice blobSource . getField
|
getSource blobSource = toText . flip Source.slice blobSource . getField
|
||||||
|
|
||||||
stripQuotes :: Text -> Text
|
|
||||||
stripQuotes = T.dropAround (`elem` ['"', '\''])
|
|
||||||
|
|
||||||
instance (Syntax.Identifier :< fs, Expression.MemberAccess :< fs) => CustomHasDeclaration (Union fs) Expression.Call where
|
instance (Syntax.Identifier :< fs, Expression.MemberAccess :< fs) => CustomHasDeclaration (Union fs) Expression.Call where
|
||||||
customToDeclaration Blob{..} _ (Expression.Call _ (Term (In fromAnn fromF), _) _ _)
|
customToDeclaration Blob{..} _ (Expression.Call _ (Term (In fromAnn fromF), _) _ _)
|
||||||
| Just (Expression.MemberAccess (Term (In leftAnn leftF)) (Term (In idenAnn _))) <- prj fromF = Just $ CallReference (getSource idenAnn) (memberAccess leftAnn leftF)
|
| Just (Expression.MemberAccess (Term (In leftAnn leftF)) (Term (In idenAnn _))) <- prj fromF = Just $ CallReference (getSource idenAnn) (memberAccess leftAnn leftF)
|
||||||
@ -191,12 +159,8 @@ class HasDeclarationWithStrategy (strategy :: Strategy) whole syntax where
|
|||||||
-- If you’re seeing errors about missing a 'CustomHasDeclaration' instance for a given type, you’ve probably listed it in here but not defined a 'CustomHasDeclaration' instance for it, or else you’ve listed the wrong type in here. Conversely, if your 'customHasDeclaration' method is never being called, you may have forgotten to list the type in here.
|
-- If you’re seeing errors about missing a 'CustomHasDeclaration' instance for a given type, you’ve probably listed it in here but not defined a 'CustomHasDeclaration' instance for it, or else you’ve listed the wrong type in here. Conversely, if your 'customHasDeclaration' method is never being called, you may have forgotten to list the type in here.
|
||||||
type family DeclarationStrategy syntax where
|
type family DeclarationStrategy syntax where
|
||||||
DeclarationStrategy Declaration.Class = 'Custom
|
DeclarationStrategy Declaration.Class = 'Custom
|
||||||
DeclarationStrategy Declaration.Function = 'Custom
|
|
||||||
-- DeclarationStrategy Declaration.Import = 'Custom
|
|
||||||
-- DeclarationStrategy Declaration.QualifiedImport = 'Custom
|
|
||||||
DeclarationStrategy Go.Syntax.SideEffectImport = 'Custom
|
|
||||||
DeclarationStrategy Ruby.Syntax.Class = 'Custom
|
DeclarationStrategy Ruby.Syntax.Class = 'Custom
|
||||||
DeclarationStrategy Ruby.Syntax.Require = 'Custom
|
DeclarationStrategy Declaration.Function = 'Custom
|
||||||
DeclarationStrategy Declaration.Method = 'Custom
|
DeclarationStrategy Declaration.Method = 'Custom
|
||||||
DeclarationStrategy Markdown.Heading = 'Custom
|
DeclarationStrategy Markdown.Heading = 'Custom
|
||||||
DeclarationStrategy Expression.Call = 'Custom
|
DeclarationStrategy Expression.Call = 'Custom
|
||||||
|
@ -1,37 +0,0 @@
|
|||||||
module Rendering.Imports.Spec (spec) where
|
|
||||||
|
|
||||||
import Analysis.Declaration (declarationAlgebra)
|
|
||||||
import Analysis.PackageDef (packageDefAlgebra)
|
|
||||||
import Rendering.Imports
|
|
||||||
|
|
||||||
import SpecHelpers
|
|
||||||
|
|
||||||
|
|
||||||
spec :: Spec
|
|
||||||
spec = parallel $ do
|
|
||||||
describe "renderToImports" $ do
|
|
||||||
xit "works for Ruby" $ do
|
|
||||||
output <- parseToImports rubyParser "test/fixtures/ruby/import-graph/app.rb"
|
|
||||||
expected <- readFileVerbatim "test/fixtures/ruby/import-graph/app.json"
|
|
||||||
toVerbatimOutput output `shouldBe` expected
|
|
||||||
|
|
||||||
xit "works for Python" $ do
|
|
||||||
output <- parseToImports pythonParser "test/fixtures/python/import-graph/main.py"
|
|
||||||
expected <- readFileVerbatim "test/fixtures/python/import-graph/main.json"
|
|
||||||
toVerbatimOutput output `shouldBe` expected
|
|
||||||
|
|
||||||
xit "works for Go" $ do
|
|
||||||
output <- parseToImports goParser "test/fixtures/go/import-graph/main.go"
|
|
||||||
expected <- readFileVerbatim "test/fixtures/go/import-graph/main.json"
|
|
||||||
toVerbatimOutput output `shouldBe` expected
|
|
||||||
|
|
||||||
xit "works for TypeScript" $ do
|
|
||||||
output <- parseToImports typescriptParser "test/fixtures/typescript/import-graph/app.ts"
|
|
||||||
expected <- readFileVerbatim "test/fixtures/typescript/import-graph/app.json"
|
|
||||||
toVerbatimOutput output `shouldBe` expected
|
|
||||||
|
|
||||||
where
|
|
||||||
toVerbatimOutput = verbatim . toOutput
|
|
||||||
parseToImports parser path = do
|
|
||||||
blob <- file path
|
|
||||||
runTask (parse parser blob >>= decorate (declarationAlgebra blob) >>= decorate (packageDefAlgebra blob) >>= render (renderToImports blob))
|
|
@ -17,7 +17,6 @@ import qualified Diffing.Interpreter.Spec
|
|||||||
import qualified Integration.Spec
|
import qualified Integration.Spec
|
||||||
import qualified Matching.Go.Spec
|
import qualified Matching.Go.Spec
|
||||||
import qualified Rendering.TOC.Spec
|
import qualified Rendering.TOC.Spec
|
||||||
import qualified Rendering.Imports.Spec
|
|
||||||
import qualified Semantic.Spec
|
import qualified Semantic.Spec
|
||||||
import qualified Semantic.CLI.Spec
|
import qualified Semantic.CLI.Spec
|
||||||
import qualified Semantic.IO.Spec
|
import qualified Semantic.IO.Spec
|
||||||
@ -44,7 +43,6 @@ main = hspec $ do
|
|||||||
describe "Diffing.Interpreter" Diffing.Interpreter.Spec.spec
|
describe "Diffing.Interpreter" Diffing.Interpreter.Spec.spec
|
||||||
describe "Matching" Matching.Go.Spec.spec
|
describe "Matching" Matching.Go.Spec.spec
|
||||||
describe "Rendering.TOC" Rendering.TOC.Spec.spec
|
describe "Rendering.TOC" Rendering.TOC.Spec.spec
|
||||||
describe "Rendering.Imports" Rendering.Imports.Spec.spec
|
|
||||||
describe "Semantic" Semantic.Spec.spec
|
describe "Semantic" Semantic.Spec.spec
|
||||||
describe "Semantic.CLI" Semantic.CLI.Spec.spec
|
describe "Semantic.CLI" Semantic.CLI.Spec.spec
|
||||||
describe "Semantic.IO" Semantic.IO.Spec.spec
|
describe "Semantic.IO" Semantic.IO.Spec.spec
|
||||||
|
Loading…
Reference in New Issue
Block a user