Skip to content
This repository has been archived by the owner on Apr 25, 2020. It is now read-only.

Commit

Permalink
Add tests for modules, check, type and info with an Explicit project
Browse files Browse the repository at this point in the history
  • Loading branch information
alang9 authored and Mitsutoshi Aoe committed Aug 2, 2016
1 parent 319587d commit e50639d
Show file tree
Hide file tree
Showing 20 changed files with 102 additions and 21 deletions.
1 change: 1 addition & 0 deletions Language/Haskell/GhcMod/Cradle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ findSpecCradle Programs { stackProgram, cabalProgram } dir = do
let cfs = [ stackCradleSpec stackProgram
, cabalCradle cabalProgram
, sandboxCradle
, explicitCradle
]
cs <- catMaybes <$> mapM (runMaybeT . ($ dir)) cfs
gcs <- filterM isNotGmCradle cs
Expand Down
20 changes: 8 additions & 12 deletions Language/Haskell/GhcMod/Find.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,6 @@ import Exception
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Gap
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Output
import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Utils
import Language.Haskell.GhcMod.World
Expand Down Expand Up @@ -120,26 +119,23 @@ loadSymbolDb' = do
return db
doLoad =<< liftIO (doesFileExist cache)

-- | Loading a file and creates 'SymbolDb'.
loadSymbolDb :: IOish m => GhcModT m SymbolDb
loadSymbolDb = do
ghcMod <- liftIO ghcModExecutable
readProc <- gmReadProcess'
out <- liftIO $ readProc ghcMod ["--verbose", "error", "dumpsym"] ""
return $!! decode out
ts <- liftIO getCurrentModTime
st <- runGmPkgGhc getGlobalSymbolTable
return SymbolDb {
sdTable = st
, sdTimestamp = ts
}

----------------------------------------------------------------
-- used 'ghc-mod dumpsym'

-- | Dumps a 'Binary' representation of 'SymbolDb' to stdout
dumpSymbol :: IOish m => GhcModT m ()
dumpSymbol = do
ts <- liftIO getCurrentModTime
st <- runGmPkgGhc $ getGlobalSymbolTable
liftIO . LBS.putStr $ encode SymbolDb {
sdTable = st
, sdTimestamp = ts
}
symbolDb <- loadSymbolDb
liftIO . LBS.putStr $ encode symbolDb

-- | Check whether given file is older than any file from the given set.
-- Returns True if given file does not exist.
Expand Down
1 change: 0 additions & 1 deletion Language/Haskell/GhcMod/Gap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,6 @@ import StringBuffer
import TcType
import Var (varType)
import System.Directory
import SysTools
#if __GLASGOW_HASKELL__ >= 800
import GHCi (stopIServ)
#endif
Expand Down
3 changes: 1 addition & 2 deletions Language/Haskell/GhcMod/Target.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ import GHC
#if __GLASGOW_HASKELL__ >= 800
import GHC.LanguageExtensions
#endif
import GHC.Paths (libdir)
import SysTools
import DynFlags
import HscTypes
Expand Down Expand Up @@ -106,7 +105,7 @@ initSession opts mdf = do
putNewSession s = do
crdl <- cradle
nhsc_env_ref <- liftIO . newIORef =<< newLightEnv (initDF crdl)
runLightGhc' nhsc_env_ref $ setSessionDynFlags =<< getSessionDynFlags
void $ runLightGhc' nhsc_env_ref $ setSessionDynFlags =<< getSessionDynFlags
gmsPut s { gmGhcSession = Just $ GmGhcSession nhsc_env_ref }


Expand Down
2 changes: 0 additions & 2 deletions Language/Haskell/GhcMod/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,9 +38,7 @@ import System.Environment
import System.FilePath
import System.IO.Temp (createTempDirectory)
import System.Process (readProcess)
import Text.Printf

import Paths_ghc_mod (getLibexecDir)
import Utils
import Prelude

Expand Down
8 changes: 6 additions & 2 deletions ghc-mod.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -94,8 +94,12 @@ Extra-Source-Files: ChangeLog
test/data/stack-project/app/*.hs
test/data/stack-project/src/*.hs
test/data/stack-project/test/*.hs
bench/data/simple-cabal/simple-cabal.cabal
bench/data/simple-cabal/*.hs
test/data/options-cradle/ghc-mod.options
test/data/options-cradle/ghc-mod.package-db-stack
test/data/options-cradle/package-db-a/package.cache
test/data/options-cradle/package-db-b/package.cache
test/data/options-cradle/package-db-c/package.cache
test/data/options-cradle/src/*.hs

Custom-Setup
Setup-Depends: base
Expand Down
12 changes: 12 additions & 0 deletions test/CheckSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -78,3 +78,15 @@ spec = do
#else
res `shouldBe` "NiceQualification.hs:4:8:Couldn't match expected type `IO ()' with actual type `[Char]'\NULIn the expression: \"wrong type\"\NULIn an equation for `main': main = \"wrong type\"\n"
#endif

it "works with explicit options" $ bracketTagged $ do
res <- runD $ checkSyntax ["src/Main.hs"]
res `shouldBe` ""

it "emits error with explicit options" $ bracketTagged $ do
res <- runD $ checkSyntax ["src/Main2.hs"]
#if __GLASGOW_HASKELL__ >= 708
res `shouldBe` "src/Main2.hs:10:11:Couldn't match expected type \8216Int\8217 with actual type \8216a0 -> a0\8217\NULProbable cause: \8216id\8217 is applied to too few arguments\NULIn the second argument of \8216(+)\8217, namely \8216id\8217\NULIn the expression: 0 + id\n"
#else
res `shouldBe` "src/Main2.hs:10:11:Couldn't match expected type `Int' with actual type `a0 -> a0'\NULIn the second argument of `(+)', namely `id'\NULIn the expression: 0 + id\NULIn an equation for `foo': foo = 0 + id\n"
#endif
1 change: 0 additions & 1 deletion test/CustomPackageDbSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@ spec = do
let tdir = "test/data/custom-cradle"
Just stack <- runD' tdir $ getCustomPkgDbStack
stack `shouldBe` [ GlobalDb
, UserDb
, PackageDb "package-db-a"
, PackageDb "package-db-b"
, PackageDb "package-db-c"
Expand Down
11 changes: 11 additions & 0 deletions test/FindSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,20 @@ import Language.Haskell.GhcMod.Find
import Test.Hspec
import TestUtils

import Dir

spec :: Spec
spec = do
describe "db <- loadSymbolDb" $ do
it "lookupSymbol' db \"head\" contains at least `Data.List'" $ do
db <- runD $ loadSymbolDb
lookupSym "head" db `shouldContain` [ModuleString "Data.List"]

it "lookupSymbol' db \"untag\" contains at least `Data.Tagged'" $ bracketTagged $ do
db <- runD $ loadSymbolDb
lookupSym "untag" db `shouldContain` [ModuleString "Data.Tagged"]

it "lookupSymbol' db \"untag\" does not contain `Data.Tagged' if not installed" $ do
withDirectory_ "test/data/options-cradle" $ do
db <- runD $ loadSymbolDb
lookupSym "untag" db `shouldNotContain` [ModuleString "Data.Tagged"]
7 changes: 7 additions & 0 deletions test/InfoSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,10 @@ spec = do
res <- runD' tdir $ types False "ImportsTH.hs" 3 8
res `shouldBe` unlines ["3 8 3 16 \"String -> IO ()\"", "3 8 3 20 \"IO ()\"", "3 1 3 20 \"IO ()\""]

it "works with a module in Explicit project type" $ bracketTagged $ do
res <- runD $ types True "src/Main.hs" 9 10
res `shouldBe` unlines ["9 8 9 14 \"() -> IO ()\"\n9 8 9 17 \"IO ()\"\n9 1 9 17 \"IO ()\""]

describe "info" $ do
it "works for non exported functions" $ do
let tdir = "test/data/non-exported"
Expand All @@ -55,3 +59,6 @@ spec = do
res <- runD' tdir $ info "ImportsTH.hs" $ Expression "bar"
res `shouldSatisfy` ("bar :: [Char]" `isPrefixOf`)

it "works with a module in Explicit project type" $ bracketTagged $ do
res <- runD $ info "src/Main.hs" $ Expression "foo"
res `shouldSatisfy` ("foo :: Int" `isPrefixOf`)
10 changes: 10 additions & 0 deletions test/ListSpec.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module ListSpec where

import Control.Applicative
import Dir
import Language.Haskell.GhcMod
import Test.Hspec
import TestUtils
Expand All @@ -12,3 +13,12 @@ spec = do
it "contains at least `Data.Map'" $ do
mdls <- runD $ lines <$> modules False
mdls `shouldContain` ["Data.Map"]

it "contains at least `Data.Tagged'" $ bracketTagged $ do
mdls <- runD $ lines <$> modules False
mdls `shouldContain` ["Data.Tagged"]

it "does not contain `Data.Tagged'" $ do
withDirectory_ "test/data/options-cradle" $ do
mdls <- runD $ lines <$> modules False
mdls `shouldNotContain` ["Data.Tagged"]
17 changes: 17 additions & 0 deletions test/TestUtils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ module TestUtils (
, shouldReturnError
, isPkgDbAt
, isPkgConfDAt
, bracketTagged
, module Language.Haskell.GhcMod.Monad
, module Language.Haskell.GhcMod.Types
) where
Expand All @@ -22,13 +23,16 @@ import Language.Haskell.GhcMod.Types
import Control.Arrow
import Control.Category
import Control.Applicative
import Control.Monad
import Control.Monad.Error (ErrorT, runErrorT)
import Control.Monad.Trans.Journal
import Data.List.Split
import Data.Label
import Data.String
import Dir
import System.FilePath
import System.Directory
import System.Process
import Test.Hspec
import Prelude hiding ((.))

Expand Down Expand Up @@ -122,3 +126,16 @@ isPkgDbAt _ _ = False

instance IsString ModuleName where
fromString = mkModuleName

-- | Bracketing function for test/data/options-cradle environment to install tagged in package-db-a
bracketTagged :: IO a -> IO a
bracketTagged m = do
withDirectory_ "test/data/options-cradle" $ do
void $ system "cabal install --global --package-db=package-db-a --prefix=$(pwd) tagged"
putStrLn "start"
void $ system "ghc-pkg list --global --user --package-db=package-db-a tagged"
putStrLn "stop"
res <- m
void $ system "ghc-pkg --package-db=package-db-a unregister tagged"
-- void $ system "cabal sandbox delete"
return res
1 change: 0 additions & 1 deletion test/data/custom-cradle/ghc-mod.package-db-stack
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
global
user
package-db-a
package-db-b
package-db-c
2 changes: 2 additions & 0 deletions test/data/options-cradle/ghc-mod.options
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
-isrc
-DINTERPRETED
5 changes: 5 additions & 0 deletions test/data/options-cradle/ghc-mod.package-db-stack
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
global
user
package-db-a
package-db-b
package-db-c
Binary file not shown.
Binary file not shown.
Binary file not shown.
12 changes: 12 additions & 0 deletions test/data/options-cradle/src/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module Main
( main
, foo
) where

import Data.Tagged

main :: IO ()
main = return ()

foo :: Int
foo = 0
10 changes: 10 additions & 0 deletions test/data/options-cradle/src/Main2.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module Main2
( main
, foo
) where

main :: IO ()
main = return ()

foo :: Int
foo = 0 + id

0 comments on commit e50639d

Please sign in to comment.