okay I only realized one thing: this test of running unboxed tuples of course won't currently work with the `ghci` mode. Does the test need to be specially notated in any way because of that?

Also my other test, parser/should_compile/read063, (and probably others) seem to be getting a failure for optimization mode just because of a NOTE in stderr? :

=====> read063(normal)
cd . && '/Users/me/modified/ghc-unboxed-prefix/compiler/stage1/ghc-inplace' -no-recomp -dcore-lint -dcmm-lint -Di386_unknown_linux -c read063.hs >read063.comp.stderr 2>&1
=====> read063(optc)
cd . && '/Users/me/modified/ghc-unboxed-prefix/compiler/stage1/ghc-inplace' -no-recomp -dcore-lint -dcmm-lint -Di386_unknown_linux -c read063.hs -O -fvia-C >read063.comp.stderr 2>&1
Actual stderr output differs from expected:
--- /dev/null   2007-12-30 14:48:00.000000000 -0500
+++ ./read063.comp.stderr.normalised    2008-01-04 08:55:51.000000000 -0500
@@ -0,0 +1 @@
+NOTE: Simplifier still going after 4 iterations; bailing out.  Size = 26
*** unexpected failure for read063(optc)



Fri Jan  4 08:48:43 EST 2008  Isaac Dupree <[EMAIL PROTECTED]>
  * add test for curried unboxed-tuple constructors
New patches:

[add test for curried unboxed-tuple constructors
Isaac Dupree <[EMAIL PROTECTED]>**20080104134843] {
hunk ./tests/ghc-regress/parser/should_run/all.T 4
+test('read004', normal, compile_and_run, [''])
addfile ./tests/ghc-regress/parser/should_run/read004.hs
hunk ./tests/ghc-regress/parser/should_run/read004.hs 1
+{-# LANGUAGE UnboxedTuples, MagicHash #-}
+
+-- should_run to make sure linking succeeds
+-- (curried unboxed tuples with both boxed
+--  and unboxed components).
+-- See Trac #1509; also Note [Primop wrappers] in Id.lhs
+
+import GHC.Exts
+
+main = do
+  case curried 9.0## 't'# of
+    (# i#, u@(), d1#, c1#, f#, d2#, c2# #)
+       -> print ( I# i#, u, D# d1#, C# c1#, F# f#, D# d2#, C# c2# )
+  print $ map_ ((#,#) True) ['a','b','c']
+
+-- try NOINLINE to make sure the currying isn't eliminated
+-- too soon, but also test the other one without NOINLINE
+-- for variety of testing
+{-# NOINLINE curried #-}
+curried :: Double# -> Char# ->
+   (# Int#, (), Double#, Char#, Float#, Double#, Char# #)
+curried = (#,,,,,,#) 3# () 4.0## 'f'# 5.0#
+
+map_ :: (a -> (# b, c #)) -> [a] -> [(b,c)]
+map_ f [] = []
+map_ f (a:as) = case f a of
+   (# b, c #) -> (b, c) : map_ f as
+
addfile ./tests/ghc-regress/parser/should_run/read004.stdout
hunk ./tests/ghc-regress/parser/should_run/read004.stdout 1
+(3,(),4.0,'f',5.0,9.0,'t')
+[(True,'a'),(True,'b'),(True,'c')]
}

Context:

[add test for prefix unboxed tuples
Isaac Dupree <[EMAIL PROTECTED]>**20080102132824] 
[Accept output for tcfail172, too
Tim Chevalier <[EMAIL PROTECTED]>**20071225190352] 
[Accept output for gadt13, gadt7
Tim Chevalier <[EMAIL PROTECTED]>**20071225185124] 
[Enable an old test for Trac 323
[EMAIL PROTECTED] 
[Test for Trac 1988
[EMAIL PROTECTED] 
[Test for Trac 1495
[EMAIL PROTECTED] 
[Add test for Trac 1981
[EMAIL PROTECTED] 
[Replace mentions of way 'opt' by the new 'optc' (often adding optasm too)
[EMAIL PROTECTED]
 
 Its really a testsuite-framework bug that these mentions of 'opt' have
 lingered so long.  They should have been rejected as a non-existent way.
 
] 
[Tests for generalised list comprehensions
[EMAIL PROTECTED] 
[Give a ticket # to expect_broken
Pepe Iborra <[EMAIL PROTECTED]>**20071220093444] 
[Unsoundness in the RTTI scheme
Pepe Iborra <[EMAIL PROTECTED]>**20071219191932] 
[add test for #1980
Simon Marlow <[EMAIL PROTECTED]>**20071218092731] 
[Fix outofmem for other 32-bit Linux platforms
Ian Lynagh <[EMAIL PROTECTED]>**20071217231845] 
[6.8 updates
Ian Lynagh <[EMAIL PROTECTED]>**20071215205108] 
[Simplify the testsuite driver
Ian Lynagh <[EMAIL PROTECTED]>**20071215195350
 Now instead of saying, e.g.
     namebase_if_compiler_lt('ghc','6.9', 'foo-6.8')
 you say
     if_compiler_lt('ghc','6.9', namebase('foo-6.8'))
] 
[add 6.8 output
Simon Marlow <[EMAIL PROTECTED]>**20071212142523] 
[Update tests for Trac #1972
[EMAIL PROTECTED] 
[More 6.8 fixes
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071213033710] 
[Make GADT tests work with 6.8 again
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071213031332] 
[Test for #1723
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071211071414] 
[Test for #1722
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071211062431] 
[Test from #1815
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071211055023] 
[accept output
Simon Marlow <[EMAIL PROTECTED]>**20071212141945] 
[add 6.8 output
Simon Marlow <[EMAIL PROTECTED]>**20071212141109] 
[countReaders001 doesn't work on Windows
Simon Marlow <[EMAIL PROTECTED]>**20071212134000] 
[fix this test on windows (avoid non-portable use of :!)
Simon Marlow <[EMAIL PROTECTED]>**20071212133745] 
[Adapt to changes in :print (contents of references)
Pepe Iborra <[EMAIL PROTECTED]>**20071209182141] 
[Remaining regression of change from GADT refinement to equalities
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071208111646
 * gadt/lazypatok fails
 * tcfail167's error message gets worse; ie, no more
   "Inaccessible case alternative: Can't match types `Char' and `Float'"
 
 Both of these are minor regressions that will be addressed in due time.
] 
[gadt: slighly changed error msg with equalities
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071208110824] 
[type families: Temporary fail
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071208110317
 - GADT3 fails with equalities instead of GADT refinement due to a known bug
] 
[Fixed by removing GADT refinements in favour of equalities
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071208110253] 
[Fixed by correcting normalisation of dicts
Manuel M T Chakravarty <[EMAIL PROTECTED]>**20071207071954] 
[Test for Trac #1370
[EMAIL PROTECTED] 
[test now passes
Simon Marlow <[EMAIL PROTECTED]>**20071206092511] 
[add test for #1959
Simon Marlow <[EMAIL PROTECTED]>**20071205152025] 
[add test for #1048
Simon Marlow <[EMAIL PROTECTED]>**20071205102619] 
[Added test for :print of a reference
Pepe Iborra <[EMAIL PROTECTED]>**20071205114017] 
[GADT9 passes now that we have fixed #1919
[EMAIL PROTECTED] 
[Skip arrowrun004 in the 6.8 branch
Ian Lynagh <[EMAIL PROTECTED]>**20071201214110] 
[Skip arrowrun002 for the 6.8 branch
Ian Lynagh <[EMAIL PROTECTED]>**20071201213910] 
[countReaders001 now passes in the 6.8 branch
Ian Lynagh <[EMAIL PROTECTED]>**20071201174337] 
[Add 6.8 branch output for break021
Ian Lynagh <[EMAIL PROTECTED]>**20071201174241] 
[Add 6.8 branch output for break003
Ian Lynagh <[EMAIL PROTECTED]>**20071201172005] 
[6.8 branch no longer needs special output for ghci026
Ian Lynagh <[EMAIL PROTECTED]>**20071201171445] 
[Update ghci024 output for the 6.8 branch
Ian Lynagh <[EMAIL PROTECTED]>**20071201171241] 
[Add tcfail187 output for the 6.8 branch
Ian Lynagh <[EMAIL PROTECTED]>**20071201170905] 
[Add 6.8-branch output for tcfail178
Ian Lynagh <[EMAIL PROTECTED]>**20071201170626] 
[tcfail175 output is now the same in 6.8 and HEAD
Ian Lynagh <[EMAIL PROTECTED]>**20071201170041] 
[Give GHC 6.8 output for tcfail168
Ian Lynagh <[EMAIL PROTECTED]>**20071201165537] 
[Add 6.8-branch output for rw
Ian Lynagh <[EMAIL PROTECTED]>**20071201164015] 
[rebindable8 is still broken in GHC 6.8
Ian Lynagh <[EMAIL PROTECTED]>**20071201163425] 
[FD1 now behaves the same in 6.8 and HEAD
Ian Lynagh <[EMAIL PROTECTED]>**20071201162525] 
[fromdos test FD1
Ian Lynagh <[EMAIL PROTECTED]>**20071201162347] 
[Add expected output for 1744
Ian Lynagh <[EMAIL PROTECTED]>**20071201162018] 
[add test for #1914
Simon Marlow <[EMAIL PROTECTED]>**20071130132214] 
[add test for #1744
Simon Marlow <[EMAIL PROTECTED]>**20071130100927] 
[Update output for change to deriving (Trac #1935)
[EMAIL PROTECTED] 
[Test for Trac #1935
[EMAIL PROTECTED] 
[add test for #1916
Simon Marlow <[EMAIL PROTECTED]>**20071128115654] 
[fix this test when CLEANUP is not done
Simon Marlow <[EMAIL PROTECTED]>**20071127123338] 
[Be more consistent in printing about framework failures
Ian Lynagh <[EMAIL PROTECTED]>**20071123181712] 
[Make Church2 fail as it (currently) should
[EMAIL PROTECTED] 
[Simple{20,22,23} now pass in the 6.8 branch
Ian Lynagh <[EMAIL PROTECTED]>**20071122134526] 
[openFile008: do "ulimit -n 1024" first
Simon Marlow <[EMAIL PROTECTED]>**20071122102223
 Hopefully fixes this on MacOS where the limit is 256 by default
 
] 
[remove the _with_prefix forms of compile_and_run, add cmd_prefix() config 
instead
Simon Marlow <[EMAIL PROTECTED]>**20071122102129] 
[add test for #1753
Simon Marlow <[EMAIL PROTECTED]>**20071122094048] 
[Update output (slight improvements on the whole)
[EMAIL PROTECTED] 
[Update output
[EMAIL PROTECTED] 
[Update test output
[EMAIL PROTECTED]
 
 This is actually *slightly* worse than before, because of the
 error-message refactoring in TcUnify. The previous message 
 reported a mis-match between
     (a->Bool) and (Bool -> Bool)
 whereas the new one only complains of mismatch between
     a   and   Bool
 Trouble is, the old one was vulnerable to the problem
 described in the comments on tcSubExp. 
 
 So I'm accepting this regression for now; let's see if
 anyone notices!
 
] 
[Update for rebindable changes (Trac #1537)
[EMAIL PROTECTED] 
[Test for Trac #1913
[EMAIL PROTECTED] 
[countReaders001 now passes
Simon Marlow <[EMAIL PROTECTED]>**20071120143539] 
[test repeated open/close of 1000 files
Simon Marlow <[EMAIL PROTECTED]>**20071120114757] 
[Tests for Trac #1825
[EMAIL PROTECTED] 
[augment ghci025 to cover #1847
[EMAIL PROTECTED]
 
 - need to test :browse! in different contexts
 - -s has disappeared, see #1799 for sorting
 - 'imported from' clarified to 'imported via'
 
] 
[Test for Trac #959
[EMAIL PROTECTED] 
[Test for Trac #1806
[EMAIL PROTECTED] 
[update to test #1873, #1360
Simon Marlow <[EMAIL PROTECTED]>**20071116155948] 
[Add -XExistentialQuantification flag (should have been there all along)
[EMAIL PROTECTED] 
[small tidyups to thie Makefile
Simon Marlow <[EMAIL PROTECTED]>**20071116131914] 
[fix this test for case sensitive filenames
Simon Marlow <[EMAIL PROTECTED]>**20071116131837] 
[1603 depends on the gcc version, which we can't easily account for, so skip
Simon Marlow <[EMAIL PROTECTED]>**20071116093428] 
[outofmem2 passes on the stable branch
Simon Marlow <[EMAIL PROTECTED]>**20071115162357] 
[add test for #1679
Simon Marlow <[EMAIL PROTECTED]>**20071115131517] 
[FIX #1840: outofmem and outofmem2 need ulimit settings to avoid filling up swap
Simon Marlow <[EMAIL PROTECTED]>**20071114164525] 
[Accept output
Pepe Iborra <[EMAIL PROTECTED]>**20071114232553
 
 The test now actually passes
 
] 
[Add test for #1892 - :info of a bkpt binding panics
Pepe Iborra <[EMAIL PROTECTED]>**20071114233829] 
[Adapt output to improvements in the TTerm pretty printer
Pepe Iborra <[EMAIL PROTECTED]>**20071114232445] 
[simplify ghci024.py, fix -fprint-bind-result, -fno-ignore-breakpoints, 
-fprint-bind-contents
[EMAIL PROTECTED]
 
 - as ghc 6.9 flags are beginning to diverge, we need
   a simpler way of specifying version-specific flags
   or settings: have two entirely separate sections,
   instead of one section with too many patches.
 
   even if that doubles the script size, it should
   be easier to edit. also add a warning that 
   ghci024.stdout is a generated file.
 
 - default for -fprint-bind-result has changed
 
 - -fno-ignore-breakpoints is gone
 
 - -fprint-bind-contents is new
 
] 
[Add test for #782
Simon Marlow <[EMAIL PROTECTED]>**20071114141111] 
[Test for Trac #1662
[EMAIL PROTECTED] 
[Test for Trac #1888
[EMAIL PROTECTED] 
[Add a test for #1827 (:print panicswith overloaded values))
Pepe Iborra <[EMAIL PROTECTED]>**20071113172048] 
[Remove some tabs in break020.hs
Pepe Iborra <[EMAIL PROTECTED]>**20071113163912] 
[Accept output
Pepe Iborra <[EMAIL PROTECTED]>**20071113163451] 
[FIX ghci024 for unregisterised, powerpc_apple_darwin, and ghc-6.8
[EMAIL PROTECTED]
  
  - for unregisterised platforms, default is '-fno-asm-mangling'
  - powerpc_apple_darwin fails on ':set -package ghc' (#1845)
  - for ghc 6.8, -fno-run-cps and -fno-convert-to-zipper-and-back
    do not exist 
 
] 
[add test for #1603
Simon Marlow <[EMAIL PROTECTED]>**20071108164056] 
[add test for #1852
Simon Marlow <[EMAIL PROTECTED]>**20071108143533] 
[Update output
Ian Lynagh <[EMAIL PROTECTED]>**20071111223835] 
[TAG 2007-11-11
Ian Lynagh <[EMAIL PROTECTED]>**20071111170042] 
Patch bundle hash:
4b19936fd0f9511b0840cf07f1cd5f75647e25e9
_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to