2018-02-07 23:20:41 +03:00
|
|
|
module Rendering.Imports.Spec where
|
|
|
|
|
|
|
|
import Analysis.Declaration (HasDeclaration, declarationAlgebra)
|
|
|
|
import Analysis.ModuleDef (HasModuleDef, moduleDefAlgebra)
|
|
|
|
import Data.Output
|
|
|
|
import Parsing.Parser
|
|
|
|
import qualified Data.ByteString as B
|
|
|
|
import qualified Data.ByteString.Char8 as BC
|
|
|
|
import qualified Data.Map as Map
|
|
|
|
import qualified Semantic.Util as Util
|
|
|
|
import Rendering.Imports
|
|
|
|
import Rendering.Renderer
|
|
|
|
import Rendering.TOC.Spec
|
|
|
|
import Semantic
|
|
|
|
import Semantic.Task
|
|
|
|
import SpecHelpers
|
2018-03-07 03:11:14 +03:00
|
|
|
import Test.Hspec (Spec, describe, it, xit, parallel, pendingWith)
|
2018-02-07 23:20:41 +03:00
|
|
|
import Test.Hspec.Expectations.Pretty
|
|
|
|
import Test.Hspec.LeanCheck
|
|
|
|
import Test.LeanCheck
|
|
|
|
|
|
|
|
|
|
|
|
spec :: Spec
|
|
|
|
spec = parallel $ do
|
|
|
|
describe "renderToImports" $ do
|
2018-03-07 03:11:14 +03:00
|
|
|
xit "works for Ruby" $ do
|
2018-02-07 23:20:41 +03:00
|
|
|
output <- parseToImports rubyParser "test/fixtures/ruby/import-graph/app.rb"
|
|
|
|
expected <- readFileVerbatim "test/fixtures/ruby/import-graph/app.json"
|
|
|
|
toVerbatimOutput output `shouldBe` expected
|
|
|
|
|
2018-03-07 03:11:14 +03:00
|
|
|
xit "works for Python" $ do
|
2018-02-07 23:20:41 +03:00
|
|
|
output <- parseToImports pythonParser "test/fixtures/python/import-graph/main.py"
|
|
|
|
expected <- readFileVerbatim "test/fixtures/python/import-graph/main.json"
|
|
|
|
toVerbatimOutput output `shouldBe` expected
|
|
|
|
|
2018-03-07 03:11:14 +03:00
|
|
|
xit "works for Go" $ do
|
2018-02-07 23:20:41 +03:00
|
|
|
output <- parseToImports goParser "test/fixtures/go/import-graph/main.go"
|
|
|
|
expected <- readFileVerbatim "test/fixtures/go/import-graph/main.json"
|
|
|
|
toVerbatimOutput output `shouldBe` expected
|
|
|
|
|
2018-03-08 22:37:41 +03:00
|
|
|
it "works for TypeScript" $ do
|
2018-02-07 23:20:41 +03:00
|
|
|
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 <- Util.file path
|
|
|
|
runTask (parse parser blob >>= decorate (declarationAlgebra blob) >>= decorate (moduleDefAlgebra blob) >>= render (renderToImports blob))
|