Skip to content

Commit

Permalink
add a test for #5149
Browse files Browse the repository at this point in the history
The only way I could ticke this with a small program was to write it
directly in .cmm (urgh).
  • Loading branch information
simonmar committed May 9, 2011
1 parent 44372d7 commit 0f9ae8c
Show file tree
Hide file tree
Showing 5 changed files with 48 additions and 0 deletions.
8 changes: 8 additions & 0 deletions tests/ghc-regress/codeGen/should_run/5149.hs
@@ -0,0 +1,8 @@
{-# LANGUAGE MagicHash,GHCForeignImportPrim,UnliftedFFITypes #-}
module Main where

import GHC.Exts

foreign import prim "f5149" f :: Int# -> Int# -> Double# -> Int#

main = print (I# (f 1# 2# 1.0##))
1 change: 1 addition & 0 deletions tests/ghc-regress/codeGen/should_run/5149.stdout
@@ -0,0 +1 @@
1
29 changes: 29 additions & 0 deletions tests/ghc-regress/codeGen/should_run/5149_cmm.cmm
@@ -0,0 +1,29 @@
#include "Cmm.h"

/* This code is carefully arranged to tickle the bug reported in #5149 */
f5149
{
D_ z;

z = D1;

W_ x,y;
x = R1;
y = R2;

if (x > y) {
goto a; /* this jump is shortcutted to g5149 */
} else {
goto b;
}

a:
jump g5149;
b:
RET_N(TO_W_(%f2i32(z)));
}

g5149
{
jump %ENTRY_CODE(Sp(0));
}
7 changes: 7 additions & 0 deletions tests/ghc-regress/codeGen/should_run/Makefile
@@ -1,3 +1,10 @@
TOP=../../../..
include $(TOP)/mk/boilerplate.mk
include $(TOP)/mk/test.mk

.PHONY: 5149
5149:
$(RM) 5149_cmm.o 5149.o 5149.hi 5149$(exeext)
$(TEST_HC) -v0 -O -c 5149_cmm.cmm
$(TEST_HC) -v0 --make -O 5149.hs 5149_cmm.o -o 5149$(exeext)
./5149
3 changes: 3 additions & 0 deletions tests/ghc-regress/codeGen/should_run/all.T
Expand Up @@ -84,3 +84,6 @@ test('3561', normal, compile_and_run, [''])
test('3677', extra_run_opts('+RTS -K8k -RTS'), compile_and_run, [''])
test('4441', normal, compile_and_run, [''])
test('5149', [ extra_clean(['5149.o', '5149.hi', '5149_cmm.o', '5149']) ],
run_command,
['$MAKE -s --no-print-directory 5149'])

0 comments on commit 0f9ae8c

Please sign in to comment.