@@ -11,12 +11,18 @@ import Control.Concurrent (forkIO, threadDelay)
1111import Control.Concurrent.MVar
1212import Control.Concurrent.STM
1313
14+ import qualified Data.ByteString.Lazy as ByteString
15+ import qualified Data.Text as Text
16+ import qualified Data.Text.Encoding as Text
17+ import Data.Function ((&) )
1418import Data.IORef
1519
1620import System.IO
1721import System.FilePath
1822import System.Directory
23+ import System.Environment (getEnvironment , unsetEnv )
1924import System.Exit
25+ import System.Process.Typed
2026#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
2127#else
2228import System.Posix.Signals
@@ -26,6 +32,7 @@ import Test.HUnit ((@?=), (@?), assertFailure)
2632import qualified Test.HUnit as HUnit
2733
2834import Language.Haskell.Interpreter
35+ import Language.Haskell.Interpreter.Unsafe
2936
3037test_reload_modified :: TestCase
3138test_reload_modified = TestCase " reload_modified" [mod_file] $ do
@@ -291,6 +298,63 @@ test_normalize_type = TestCase "normalize_type" [mod_file] $ do
291298 ," type instance Foo x = ()" ]
292299 mod_file = " TEST_NormalizeType.hs"
293300
301+ test_package_db :: IOTestCase
302+ test_package_db = IOTestCase " package_db" [dir] $ \ wrapInterp -> do
303+ setup
304+ ghcVersionOutput <- readProcessStdout_ $ proc " ghc" [" --version" ]
305+ let ghcVersion
306+ :: String
307+ ghcVersion
308+ = ghcVersionOutput
309+ -- "The Glorious Glasgow Haskell Compilation System, version 8.8.4" :: ByteString.Lazy
310+ & ByteString. toStrict
311+ -- "The Glorious Glasgow Haskell Compilation System, version 8.8.4" :: ByteString
312+ & Text. decodeUtf8
313+ -- "The Glorious Glasgow Haskell Compilation System, version 8.8.4" :: Text
314+ & Text. unpack
315+ -- "The Glorious Glasgow Haskell Compilation System, version 8.8.4" :: String
316+ & words
317+ -- ["The","Glorious","Glasgow","Haskell","Compilation","System,","version","8.8.4"]
318+ & last
319+ -- "8.8.4"
320+ let pkgdb = dir </> " dist-newstyle" </> " packagedb" </> (" ghc-" ++ ghcVersion)
321+ ghc_args = [" -package-db=" ++ pkgdb]
322+
323+ -- stack sets GHC_ENVIRONMENT to a file which pins down the versions of
324+ -- all the packages we can load, and since it does not list my-package,
325+ -- we cannot load it.
326+ unsetEnv " GHC_ENVIRONMENT"
327+
328+ wrapInterp (unsafeRunInterpreterWithArgs ghc_args) $ do
329+ -- succeeds (setImports [mod]) @@? "module from package-db must be visible"
330+ setImports [mod ]
331+ --
332+ where pkg = " my-package"
333+ dir = pkg
334+ mod_file = dir </> mod <.> " hs"
335+ mod = " MyModule"
336+ cabal_file = dir </> pkg <.> " cabal"
337+ setup = do createDirectory dir
338+ writeFile cabal_file $ unlines
339+ [ " cabal-version: 2.4"
340+ , " name: " ++ pkg
341+ , " version: 0.1.0.0"
342+ , " "
343+ , " library"
344+ , " exposed-modules: " ++ mod
345+ ]
346+ writeFile mod_file $ unlines
347+ [ " {-# LANGUAGE NoImplicitPrelude #-}"
348+ , " module " ++ mod ++ " where"
349+ ]
350+ env <- getEnvironment
351+ runProcess_
352+ $ setWorkingDir dir
353+ $ -- stack sets GHC_PACKAGE_PATH, but cabal complains
354+ -- that it cannot run if that variable is set.
355+ setEnv (filter ((/= " GHC_PACKAGE_PATH" ) . fst ) env)
356+ $ proc " cabal" [" build" ]
357+
294358-- earlier versions of hint were accidentally overwriting the signal handlers
295359-- for ^C and others.
296360--
@@ -299,9 +363,9 @@ test_normalize_type = TestCase "normalize_type" [mod_file] $ do
299363-- succeeds when executed from ghci and ghcid, regardless of whether the problematic
300364-- behaviour has been fixed or not.
301365test_signal_handlers :: IOTestCase
302- test_signal_handlers = IOTestCase " signal_handlers" [] $ \ runInterp -> do
366+ test_signal_handlers = IOTestCase " signal_handlers" [] $ \ wrapInterp -> do
303367#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
304- runInterp $ do
368+ wrapInterp runInterpreter $ do
305369 pure ()
306370#else
307371 signalDetectedRef <- newIORef False
@@ -311,7 +375,7 @@ test_signal_handlers = IOTestCase "signal_handlers" [] $ \runInterp -> do
311375 acquire = installHandler sigINT (Catch detectSignal) Nothing
312376 release handler = installHandler sigINT handler Nothing
313377 r <- bracket acquire release $ \ _ -> do
314- runInterp $ do
378+ wrapInterp runInterpreter $ do
315379 liftIO $ do
316380 r <- try $ do
317381 raiseSignal sigINT
@@ -357,6 +421,7 @@ tests = [test_reload_modified
357421
358422ioTests :: [IOTestCase ]
359423ioTests = [test_signal_handlers
424+ ,test_package_db
360425 ]
361426
362427main :: IO ()
@@ -406,29 +471,40 @@ noInterpreterError :: Either InterpreterError a -> IO a
406471noInterpreterError (Left e) = assertFailure (show e)
407472noInterpreterError (Right a) = pure a
408473
409- data IOTestCase = IOTestCase String [FilePath ] ((Interpreter () -> IO (Either InterpreterError () )) -> IO (Either InterpreterError () ))
474+ data IOTestCase = IOTestCase
475+ String -- test name
476+ [FilePath ] -- temporary files and folders to delete after the test
477+ ( ( (Interpreter () -> IO (Either InterpreterError () ))
478+ -> (Interpreter () -> IO (Either InterpreterError () ))
479+ ) -- please wrap your 'runInterpreter' calls with this
480+ -> IO (Either InterpreterError () ) -- create temporary files and run the test
481+ )
410482
411483runIOTests :: Bool -> [IOTestCase ] -> IO HUnit. Counts
412484runIOTests sandboxed = HUnit. runTestTT . HUnit. TestList . map build
413- where build (IOTestCase title tmps test) = HUnit. TestLabel title $
414- HUnit. TestCase test_case
485+ where build (IOTestCase title tmps test)
486+ = HUnit. TestLabel title $ HUnit. TestCase test_case
415487 where test_case = go `finally` clean_up
416488 clean_up = mapM_ removeIfExists tmps
417- go = do r <- test ( \ body -> runInterpreter
418- (when sandboxed setSandbox >> body))
489+ wrapInterp runInterp body = runInterp (when sandboxed setSandbox >> body)
490+ go = do r <- test wrapInterp
419491 noInterpreterError r
420492 removeIfExists f = do existsF <- doesFileExist f
421493 if existsF
422494 then removeFile f
423495 else
424496 do existsD <- doesDirectoryExist f
425497 when existsD $
426- removeDirectory f
498+ removeDirectoryRecursive f
427499
428- data TestCase = TestCase String [FilePath ] (Interpreter () )
500+ data TestCase = TestCase
501+ String -- test name
502+ [FilePath ] -- temporary files and folders to delete after the test
503+ (Interpreter () ) -- create temporary files and run the test
429504
430505runTests :: Bool -> [TestCase ] -> IO HUnit. Counts
431506runTests sandboxed = runIOTests sandboxed . map toIOTestCase
432507 where
433508 toIOTestCase :: TestCase -> IOTestCase
434- toIOTestCase (TestCase title tmps test) = IOTestCase title tmps ($ test)
509+ toIOTestCase (TestCase title tmps test) = IOTestCase title tmps $ \ wrapInterp -> do
510+ wrapInterp runInterpreter test
0 commit comments