[commit: testsuite] master: Use a proper executable (rather than a shell script) in T6106 (fdd8f9d)
Ian Lynagh
igloo at earth.li
Sun Feb 3 21:03:45 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/fdd8f9d73f4c4e93e0ae3f53ac2b61000b9d3e0e
>---------------------------------------------------------------
commit fdd8f9d73f4c4e93e0ae3f53ac2b61000b9d3e0e
Author: Ian Lynagh <ian at well-typed.com>
Date: Sun Feb 3 18:41:55 2013 +0000
Use a proper executable (rather than a shell script) in T6106
Fixes the test on Windows
>---------------------------------------------------------------
tests/ghci/scripts/Makefile | 5 +++++
tests/ghci/scripts/T6106.script | 2 +-
tests/ghci/scripts/T6106_preproc.hs | 17 +++++++++++++++++
tests/ghci/scripts/T6106_preproc.sh | 7 -------
tests/ghci/scripts/all.T | 8 +++++++-
5 files changed, 30 insertions(+), 9 deletions(-)
diff --git a/tests/ghci/scripts/Makefile b/tests/ghci/scripts/Makefile
index 1fe7025..73f6203 100644
--- a/tests/ghci/scripts/Makefile
+++ b/tests/ghci/scripts/Makefile
@@ -34,3 +34,8 @@ ghci037:
ghci056_setup:
'$(TEST_HC)' $(TEST_HC_OPTS) -c ghci056_c.c
+
+.PHONY: T6106_prep
+T6106_prep:
+ '$(TEST_HC)' $(TEST_HC_OPTS) -v0 --make T6106_preproc
+
diff --git a/tests/ghci/scripts/T6106.script b/tests/ghci/scripts/T6106.script
index 1b071ec..be6de46 100644
--- a/tests/ghci/scripts/T6106.script
+++ b/tests/ghci/scripts/T6106.script
@@ -3,7 +3,7 @@
:l
:shell rm -f T6106.hs
-:shell echo "{-# OPTIONS_GHC -F -pgmF ./T6106_preproc.sh #-}" >T6106.hs
+:shell echo "{-# OPTIONS_GHC -F -pgmF ./T6106_preproc #-}" >T6106.hs
:shell echo "module T6106 where" >>T6106.hs
:load T6106.hs
-- second one should fail:
diff --git a/tests/ghci/scripts/T6106_preproc.hs b/tests/ghci/scripts/T6106_preproc.hs
new file mode 100644
index 0000000..fd2a55a
--- /dev/null
+++ b/tests/ghci/scripts/T6106_preproc.hs
@@ -0,0 +1,17 @@
+
+import Control.Concurrent
+import Data.ByteString as BS
+import System.Environment
+
+main :: IO ()
+main = do args <- getArgs
+ case args of
+ [x, y, z] -> f x y z
+ _ -> error ("Bad args: " ++ show args)
+
+f :: String -> String -> String -> IO ()
+f x y z = do bs <- BS.readFile y
+ BS.writeFile z bs
+ threadDelay 1000000
+ Prelude.writeFile x "FAIL"
+
diff --git a/tests/ghci/scripts/T6106_preproc.sh b/tests/ghci/scripts/T6106_preproc.sh
deleted file mode 100755
index 56ca608..0000000
--- a/tests/ghci/scripts/T6106_preproc.sh
+++ /dev/null
@@ -1,7 +0,0 @@
-#!/bin/sh
-#
-# file T6106_preproc.sh
-#
-cat $2 > $3
-sleep 1
-echo "FAIL" >$1
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index 659a275..b4dd448 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -128,7 +128,13 @@ test('T6027ghci', normal, ghci_script, ['T6027ghci.script'])
test('T6007', normal, ghci_script, ['T6007.script'])
test('T6091', normal, ghci_script, ['T6091.script'])
-test('T6106', extra_clean(['T6106.hs']), ghci_script, ['T6106.script'])
+test('T6106',
+ [extra_clean(['T6106.hs',
+ 'T6106_preproc.hi', 'T6106_preproc.o',
+ 'T6106_preproc', 'T6106_preproc.exe']),
+ pre_cmd('$MAKE -s --no-print-directory T6106_prep')],
+ ghci_script,
+ ['T6106.script'])
test('T6105', normal, ghci_script, ['T6105.script'])
test('T7117', normal, ghci_script, ['T7117.script'])
test('ghci058',
More information about the ghc-commits
mailing list