[commit: testsuite] master: Test Trac #8628 (e5a95b0)

git at git.haskell.org git at git.haskell.org
Fri Jan 3 16:34:09 UTC 2014


Repository : ssh://git@git.haskell.org/testsuite

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/e5a95b0ae2318ecb2deda26e1421cf4b5c8327ab/testsuite

>---------------------------------------------------------------

commit e5a95b0ae2318ecb2deda26e1421cf4b5c8327ab
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Jan 3 16:33:59 2014 +0000

    Test Trac #8628


>---------------------------------------------------------------

e5a95b0ae2318ecb2deda26e1421cf4b5c8327ab
 tests/ghc-api/Makefile     |    4 ++++
 tests/ghc-api/T8628.hs     |   33 +++++++++++++++++++++++++++++++++
 tests/ghc-api/T8628.stdout |    3 +++
 tests/ghc-api/all.T        |    3 +++
 4 files changed, 43 insertions(+)

diff --git a/tests/ghc-api/Makefile b/tests/ghc-api/Makefile
index 808990c..855b774 100644
--- a/tests/ghc-api/Makefile
+++ b/tests/ghc-api/Makefile
@@ -13,6 +13,10 @@ T8639_api: clean
 	'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc T8639_api
 	./T8639_api "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
 
+T8628: clean
+	'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc T8628
+	./T8628 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
+
 .PHONY: clean T6145
 
 
diff --git a/tests/ghc-api/T8628.hs b/tests/ghc-api/T8628.hs
new file mode 100644
index 0000000..203d328
--- /dev/null
+++ b/tests/ghc-api/T8628.hs
@@ -0,0 +1,33 @@
+module Main where
+
+import System.IO
+import DynFlags
+import GHC
+import Exception
+import Module
+import FastString
+import MonadUtils
+import Outputable
+import Bag (filterBag,isEmptyBag)
+import System.Directory (removeFile)
+import System.Environment( getArgs )
+import PrelNames
+
+main :: IO()
+main
+  = do  [libdir] <- getArgs
+        ok <- runGhc (Just libdir) $ do
+          dflags <- getSessionDynFlags
+          setSessionDynFlags dflags
+          liftIO (setUnsafeGlobalDynFlags dflags)
+
+          setContext [ IIDecl (simpleImportDecl pRELUDE_NAME)
+                     , IIDecl (simpleImportDecl (mkModuleNameFS (fsLit "System.IO")))]
+          runDecls "data X = Y ()"
+          runStmt "print True" RunToCompletion
+          gtry $ runStmt "print (Y ())" RunToCompletion :: GhcMonad m => m (Either SomeException RunResult)
+          runDecls "data X = Y () deriving Show"
+          _ <- dynCompileExpr "'x'"
+          runStmt "print (Y ())" RunToCompletion
+          runStmt "System.IO.hFlush System.IO.stdout" RunToCompletion
+        print "done"
diff --git a/tests/ghc-api/T8628.stdout b/tests/ghc-api/T8628.stdout
new file mode 100644
index 0000000..d18820e
--- /dev/null
+++ b/tests/ghc-api/T8628.stdout
@@ -0,0 +1,3 @@
+True
+Y ()
+"done"
diff --git a/tests/ghc-api/all.T b/tests/ghc-api/all.T
index 998bcd7..1f83dcd 100644
--- a/tests/ghc-api/all.T
+++ b/tests/ghc-api/all.T
@@ -5,3 +5,6 @@ test('T6145', when(fast(), skip),
 test('T8639_api', when(fast(), skip),
               run_command,
               ['$MAKE -s --no-print-directory T8639_api'])
+test('T8628', when(fast(), skip),
+              run_command,
+              ['$MAKE -s --no-print-directory T8628'])



More information about the ghc-commits mailing list