Make sure the liquid haskell test files are generated for unit-test

We must run the liquid exe to generate results to be parsed.
This commit is contained in:
Alan Zimmerman 2019-11-06 21:31:05 +00:00
parent 7cf1295a28
commit a1b2f8c5d8
2 changed files with 23 additions and 14 deletions

View File

@ -166,10 +166,19 @@ runLiquidHaskell fp = do
cp = (shell cmd) { cwd = Just dir }
-- logm $ "runLiquidHaskell:cmd=[" ++ cmd ++ "]"
mpp <- lookupEnv "GHC_PACKAGE_PATH"
mge <- lookupEnv "GHC_ENVIRONMENT"
-- logm $ "runLiquidHaskell:mpp=[" ++ show mpp ++ "]"
-- env <- getEnvironment
-- logm $ "runLiquidHaskell:env=[" ++ show env ++ "]"
(ec,o,e) <- bracket
(unsetEnv "GHC_PACKAGE_PATH")
(\_ -> mapM_ (setEnv "GHC_PACKAGE_PATH") mpp)
(do
unsetEnv "GHC_ENVIRONMENT"
unsetEnv "GHC_PACKAGE_PATH"
)
(\_ -> do
mapM_ (setEnv "GHC_PACKAGE_PATH") mpp
mapM_ (setEnv "GHC_ENVIRONMENT" ) mge
)
(\_ -> readCreateProcessWithExitCode cp "")
-- logm $ "runLiquidHaskell:v=" ++ show (ec,o,e)
return $ Just (ec,[o,e])

View File

@ -3,6 +3,7 @@
module LiquidSpec where
import Data.Aeson
import Data.List
import qualified Data.ByteString.Lazy as BS
import qualified Data.Text as T
import qualified Data.Text.IO as T
@ -11,8 +12,10 @@ import Data.Maybe (isJust)
import Haskell.Ide.Engine.MonadTypes
import Haskell.Ide.Engine.Plugin.Liquid
import System.Directory
import System.Exit
import System.FilePath
import Test.Hspec
import Control.Monad.IO.Class
main :: IO ()
main = hspec spec
@ -28,18 +31,15 @@ spec = do
-- ---------------------------------
-- AZ: this test has been moved to func-tests, stack > 2.1 sets
-- its own package environment, we can't run it from here.
-- -- This produces some products in /test/testdata/liquid/.liquid/ that is used in subsequent test
-- it "runs the liquid haskell exe" $ do
-- let
-- fp = cwd </> "test/testdata/liquid/Evens.hs"
-- -- fp = "/home/alanz/tmp/haskell-proc-play/Evens.hs"
-- -- uri = filePathToUri fp
-- Just (ef, (msg:_)) <- runLiquidHaskell fp
-- msg `shouldSatisfy` isPrefixOf "RESULT\n[{\"start\":{\"line\":9,\"column\":1},\"stop\":{\"line\":9,\"column\":8},\"message\":\"Error: Liquid Type Mismatch\\n Inferred type\\n VV : {v : Int | v == (7 : int)}\\n \\n not a subtype of Required type\\n VV : {VV : Int | VV mod 2 == 0}\\n"
-- ef `shouldBe` ExitFailure 1
-- This produces some products in /test/testdata/liquid/.liquid/
-- that are used in subsequent test
it "runs the liquid haskell exe" $ do
let
fp = cwd </> "test/testdata/liquid/Evens.hs"
Just (ef, (msg:_)) <- runLiquidHaskell fp
liftIO $ putStrLn $ "msg=" ++ msg
msg `shouldSatisfy` isPrefixOf "RESULT\n[{\"start\":{\"line\""
ef `shouldBe` ExitFailure 1
-- ---------------------------------
it "gets annot file paths" $ do