[Haskell-cafe] ghc 6.8.1 bug?

SevenThunders mattcbro at earthlink.net
Wed Nov 28 21:45:11 EST 2007



SevenThunders wrote:
> 
> 
> 
> The new behavior is that under certain conditions a certain matrix inner
> product produces undefined floats, that should not be there. 
> 

I now have a simple example that I have posted as ticket number 1944 for ghc
6.8.1.  The behavior is that if I link to an external cblas .dll file and do
a simple matrix multiply I get NaNs in the answer.  However this only seems
to happen after I call the round function.  The behavior does not occur for
ghc 6.6.1.

  I will show the source files that cause this below.

Test2.hs:

module Main where

foreign import ccall unsafe "test2.h iprod" iprod :: IO()

main = do
    let base = round 0.03
    print $ "rounded base = " ++ (show base)
    iprod


The c source file ctest2.c:
#include <math.h>
#include <stdio.h>
#include "ctest2.h"

#define N 2
#define N4 8
/* 4 x N matrix */
double A[N4]  ;
/* N x 1 matrix */
double B[N]  ;
double C[4] = {0.0,0.0,0.0,0.0} ;


void iprod(void)
{
    int k ;
    double sum ;
    for (k = 0 ; k < N4 ; k++) {
	A[k] = 1.0 ;
    }
    for (k = 0 ; k < N ; k++) {
	B[k] = 1.0 ;
    }
    cblas_dgemm(CblasColMajor, CblasNoTrans, CblasNoTrans, 4, 1, N,  1.0, A,
4, B, N, 0.0, C, 4) ; 
    for (k = 0 ; k < 4 ; k++) {
    printf("C[%d] = %g\n", k, C[k]) ;
    }
}

The .h include file ctest2.h:
enum CBLAS_ORDER {CblasRowMajor=101, CblasColMajor=102 };
enum CBLAS_TRANSPOSE {CblasNoTrans=111, CblasTrans=112, CblasConjTrans=113,
                         AtlasConj=114};
enum CBLAS_UPLO  {CblasUpper=121, CblasLower=122};
enum CBLAS_DIAG  {CblasNonUnit=131, CblasUnit=132};
enum CBLAS_SIDE  {CblasLeft=141, CblasRight=142};


void cblas_dgemm(const enum CBLAS_ORDER Order, const enum CBLAS_TRANSPOSE
TransA,
                 const enum CBLAS_TRANSPOSE TransB, const int M, const int
N,
                 const int K, const double alpha, const double *A,
                 const int lda, const double *B, const int ldb,
                 const double beta, double *C, const int ldc);


void iprod(void) ;

The .bat file I used to compile this:
set CLIB=atlas
set TopFile=Test2
set csrc=ctest2.c
set OutFile=%TopFile%.exe
dlltool.exe -D %CLIB%.dll -l %CLIB%.lib
set XFLAGS=-threaded -O -XForeignFunctionInterface
rem set XFLAGS=-prof -auto-all 
rem -caf-all
ghc %XFLAGS% -I. -I..\matrixstack --make %TopFile%.hs %csrc% -o %OutFile%
-optl-l%CLIB% -optl-L"."


and finally the output which prints the NaNs after calling Test2.exe,
"rounded base =
C[0] = -1.#IND
C[1] = 2
C[2] = 2
C[3] = -1.#IND


-- 
View this message in context: http://www.nabble.com/ghc-6.8.1-bug--tf4810375.html#a14018323
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.



More information about the Haskell-Cafe mailing list