[Search for users] [Overall Top Noters] [List of all Conferences] [Download this site]

Conference nicctr::kap-users

Title:Kuck Associates Preprocessor Users
Notice:KAP V2.1 (f90,f77,C) SSB-kits - see note 2
Moderator:HPCGRP::DEGREGORY
Created:Fri Nov 22 1991
Last Modified:Fri Jun 06 1997
Last Successful Update:Fri Jun 06 1997
Number of topics:390
Total number of notes:1440

368.0. "Problem with KAP f90 -lc=blas" by NETRIX::"jarkko.hietaniemi@fno.mts.dec.com" (Jarkko Hietaniemi) Tue Feb 25 1997 09:00

Where should I report this? A customer of my customer found quite
clear bug in the KAPF90:

--- clip clap ---
The following code does not compile with the KAP and the option "-lc=blas".
The normal f90 compiles the code all right but the resulting code is *slow*.

PROGRAM mm
  IMPLICIT NONE
  INTEGER, PARAMETER :: m = 550, n = 450, p = 500

  INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND(12)
  REAL(KIND=dp) :: a(m,n), b(n,p), c(m,p)
  REAL :: time1, time2
  INTEGER :: i, j

! Init the matrices
  a = 1.5
  b = 3.0

! Do the matrix multiplication
  time1 = secnds(0.0)
  CALL matrix_mult(a, b, c)
  time2 = secnds(0.0)

  WRITE (*,*) 'time in seconds: ', time2 - time1

CONTAINS

  SUBROUTINE matrix_mult(a, b, c)
    IMPLICIT NONE
    INTEGER :: lda, ldb, ll
    REAL(KIND=dp), DIMENSION(:,:) :: a, b, c
    INTEGER :: i, j, k

    DO j = 1, SIZE(b,2)
      DO i = 1, SIZE(a,1)
        c(i,j) = 0.0
        DO k = 1, SIZE(b,1)
          c(i,j) = c(i,j) + a(i,k)*b(k,j)
        END DO
      END DO
    END DO
  END SUBROUTINE matrix_mult

END PROGRAM mm

The compilation command is:

kf90 -fkapargs='-lc=blas' mm2.f90 -ldxml -o mm.exe

The error message is:

 KAP/Digital_UA_F90   3.0 k271210 960605     17-Feb-1997   14:20:25


 ### Internal Error : niceprint-illegal exprs
 *** while processing routine MATRIX_MULT

 *** Version 3.0 k271210 960605
 *** Version 3.0 k271210 960605

 KAP -- Fatal Error
Exit 3

If an EXTERNAL subroutine is used, the KAP works fine (please find
the code appended).



PROGRAM mm
  IMPLICIT NONE
  INTEGER, PARAMETER :: m = 550, n = 450, p = 500
  INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND(12)
  REAL(KIND=dp) :: a(m,n), b(n,p), c(m,p)
  REAL :: time1, time2
  INTEGER :: i, j
  EXTERNAL matrix_mult

! Init the matrices
  a = 1.5
  b = 3.0

! DO the matrix multiplication
  time1 = secnds(0.0)
  CALL matrix_mult(a, m, b, n, c, p)
  time2 = secnds(0.0)

  WRITE (*,*) 'time in seconds: ', time2 - time1

END PROGRAM mm

SUBROUTINE matrix_mult(a, lda, b, ldb, c, ll)
  IMPLICIT NONE
  INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND(12)
  INTEGER :: lda, ldb, ll
 REAL(KIND=dp) :: a(lda,ldb), b(ldb,ll), c(lda,ll)
  INTEGER :: i, j, k

  DO j = 1, ll
    DO i = 1, lda
      c(i,j) = 0.0
      DO k = 1, ldb
        c(i,j) = c(i,j) + a(i,k)*b(k,j)
      END DO
    END DO
  END DO
END SUBROUTINE matrix_mult


[Posted by WWW Notes gateway]
T.RTitleUserPersonal
Name
DateLines
368.1working on this nowHPCGRP::DEGREGORYKaren 223-5801Tue Feb 25 1997 16:223
Sorry about this, we are looking at it now.

Karen
368.2try -lc=blas23HPCGRP::DEGREGORYKaren 223-5801Tue Feb 25 1997 17:2116
While we are working on the bug, you should be able to process the code
without error using -lc=blas23.

oursmp> kapf90 -lc=blas23 lc.f
 KAP/Digital_UA_F90   3.1 k271526 970117     25-Feb-1997   13:24:45
0 errors in file lc.f
oursmp> kapf90 -lc=blas12 lc.f
 KAP/Digital_UA_F90   3.1 k271526 970117     25-Feb-1997   13:24:50


 ### Internal Error : niceprint-illegal exprs
 *** while processing routine MATRIX_MULT

 *** Version 3.1 k271526 970117

 KAP -- Fatal Error
368.3Thanks for quick reply!NETRIX::"jarkko.hietaniemi@fno.mts.dec.com"Jarkko HietaniemiWed Feb 26 1997 05:203
I'll tell my customer about the workaround asap.

[Posted by WWW Notes gateway]