Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/b2c5047da15f0b6441db7e615a84ce64d0f77890

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

commit b2c5047da15f0b6441db7e615a84ce64d0f77890
Author: Johan Tibell <johan.tib...@gmail.com>
Date:   Thu Dec 6 11:26:38 2012 -0800

    Add test for -funbox-strict-primitive-fields

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

 .../should_compile/UnboxStrictPrimitiveFields.hs   |   28 ++++++++++++++++++++
 tests/typecheck/should_compile/all.T               |    1 +
 2 files changed, 29 insertions(+), 0 deletions(-)

diff --git 
a/tests/ghc-regress/typecheck/should_compile/UnboxStrictPrimitiveFields.hs 
b/tests/ghc-regress/typecheck/should_compile/UnboxStrictPrimitiveFields.hs
new file mode 100644
index 0000000..e1549bd
--- /dev/null
+++ b/tests/ghc-regress/typecheck/should_compile/UnboxStrictPrimitiveFields.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE MagicHash #-}
+{-# OPTIONS_GHC -funbox-strict-primitive-fields #-}
+module Test where
+
+import GHC.Exts
+
+-- The following should be unboxed automatically:
+data A = A Int#
+data B = B !A
+data C = C !()
+data D = D !B
+data E = E !D !D
+
+d = D (B (A 0#))
+e = E d d
+
+data F = F Int#
+newtype G = G F
+data H = H !G !G
+
+h = H (G (F 1#)) (G (F 1#))
+
+-- This should not be unboxed:
+
+data I = I !H !H
+
+i = I h h
+
diff --git a/tests/typecheck/should_compile/all.T 
b/tests/typecheck/should_compile/all.T
index d350307..cb24574 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -394,3 +394,4 @@ test('holes', normal, compile, ['-fdefer-type-errors'])
 test('holes2', normal, compile, ['-fdefer-type-errors'])
 test('holes3', normal, compile_fail, [''])
 test('T7408', normal, compile, [''])
+test('UnboxStrictPrimitiveFields', normal, compile, [''])



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to