[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

369.0. "KAP produces strange warning then forgets to define a var." by PEACHS::LAMPERT (Pat Lampert, UNIX Applications Support, 343-1050) Thu Mar 06 1997 18:06

Awhile back a customer of ours, llnl, was instructed to use KAP for 
F77 to work around a KAP F90 problem...

KAP 3.1,  F90 4.1, UNIX 4.0a

I just want to confirm that this is a bug..

Take the following small example (boiled down from 1200 lines of
code from llnl)...


      subroutine cupara ( mn,kk)

      IMPLICIT NONE

      REAL W1, TC


      INTEGER KK, MN, K, I, LEN1, LEN, IY


c
      dimension tc(mn,kk)
c
      dimension w1(mn),iy(mn)

        len = 10
        len1 = 10

c*$* assert no last value needed (w1)
      do 530 k = 1, kk
      do 520 i = 1, len1
      w1(i) = tc(i,k)
  520 continue
      do 525 i = 1, len
      tc(i,k) = w1(iy(i))
  525 continue
  530 continue
c
      return
      end


If you compile this with KAP (note the assertion) you get the
following warning:

cdeman.alf.dec.com> kapf -conc -real=8 dum1.f -cmp=dum.cmp.f
 KAP/Digital_UA_F   3.1 k271615 961104     06-Mar-1997   14:49:02

     ###       do 530 k = 1, kk
     ### in line 20 procedure CUPARA of file dum1.f ###
Stack usage for routine PKCUPARA_ is unknown, parallel STACKSIZE must be at leas
t 28 bytes.
0 errors in file dum1.f
 KAP -- Syntax Warnings Detected


I went through the User's Guide and only found one warning that looks
like this. The manual (HTML on CD) had a hyperlink to the section 
showing how to define KMP_STACKSIZE.  I did, but the warning persisted.

After compilation, and possibly as a result of the warning, F90
now generates a warning on the preprocessed kap file:


cdeman.alf.dec.com> f90 -r8 -automatic -c dum.cmp.f
f90: Warning: dum.cmp.f, line 86: Variable MN is used before its value has been
defined
       DO II5=1,MN
-------^


The original file compiles just fine:

cdeman.alf.dec.com> f90 -r8 -automatic -c dum1.f
cdeman.alf.dec.com>

Thanks in advance...

Pat
T.RTitleUserPersonal
Name
DateLines
369.1I'm checking on this....HPCGRP::DEGREGORYKaren 223-5801Mon Mar 10 1997 16:420
369.2the warning makes sense, however you can ignore the size....HPCGRP::DEGREGORYKaren 223-5801Tue Mar 11 1997 13:5040
Pat -

The currently shipping KAP F77 gives this warning but the currently shipping
KAP F90 does not.  The warning message should be given and the fact that
KAP F90 doesn't give a warning is a bug.

Here is the explanation from KAI as to why they are giving the warning.
Note that in the next release of KAP the warning message will not include
a stack size...


> 
> The current message coming out of the next release of KAP is:
> 
>  KAP/Digital_UA_F   66.66 k666666T 66666   10-Mar-1997   13:28:18
> 
>      ###       do 530 k = 1, kk
>      ### in line 15 procedure CUPARA of file stk.f ### 
> warning: Stack usage for routine PKCUPARA_ is unknown, parallel STACKSIZE should be checked.
> KAP/Digital_UA_F 66.66 k666666T 66666: 0 errors in file stk.f
> 
> The reason for this message is that KAP has done something very sophisticated.
> It has made the variable W1 local to each thread even though it does not know the
> actual size of W1.  The variable W1 is a "Cray AUTOMATIC", it's size is calculated
> at the the time the subroutine is entered.
> 
> KAP can not check the KMP_STACKSIZE environment variable to see if it is large
> enough because it does not know the size of the variable W1.  
> 
> The warning is issued to alert the user that a variable amount of stack space
> is used by this routine and it might overflow the thread stack at runtime.
> 
> (The old error messages included the STATIC compoment of the stack usage, which
>  was a least 28 bytes, this was deemed to be useless information and was
>  deleted from the error messages).
> 
> I believe the reason that alphaosff90 does not issue this warning message is
> probably a bug.  This kind of check should also be inserted into the F90
> code generation.
> 
369.3Thanks for the explaination of the warning, but what about the missing var?PEACHS::LAMPERTPat Lampert, UNIX Applications Support, 343-1050Tue Mar 11 1997 18:43120
OK I understand the warning now. Thanks.

The ultimate problem, though, is that KAP generates what
appears to be a coding error in the output file.

The loop...


       DO II5=1,MN
        W12(II5) = W11(II5)
       END DO


uses a variable that is never defined.  (MN).  Shouldnt this
be MN1?

Here is the result of processing the program in .0 with KAP.

C     KAP/Digital_UA_F      3.1 k271615 961104  o5r3so3  06-Mar-1997 14:49:02
      SUBROUTINE CUPARA ( MN, KK )
 
       IMPLICIT NONE
       INTEGER II4, II3, II2
       PARAMETER (II4 = 5, II3 = 0, II2 = 14)
       EXTERNAL mppfkd, mppfrk, PKCUPARA_
       INTEGER mppfkd
       INTEGER II1
       PARAMETER (II1 = 10)
 
       REAL W1, TC
   
 
       INTEGER KK, MN, K, I, LEN1, LEN, IY
 
 
c
       DIMENSION TC(MN,KK)
c
       DIMENSION W1(MN), IY(MN)
 
 
C*$* ASSERTNOLASTVALUENEEDED ( W1 )
       IF (KK .GT. II2 .AND. mppfkd () .EQ. II3) THEN
        CALL mppfrk (PKCUPARA_,II4,TC,KK,IY,W1,MN)
       ELSE
C!!!! PARALLEL IF (KK .GT. 14) SHARED (KK,TC,IY,W1) LOCAL (K,I)
C!!!! PDO FIRSTLOCAL (W1)
        DO K=1,KK
         DO I=1,II1
          W1(I) = TC(I,K)
         END DO
         DO I=1,II1
          TC(I,K) = W1(IY(I))
         END DO
        END DO
C!!!! END PDO NOWAIT
C!!!! END PARALLEL 
       END IF
c
       RETURN 
      END
C     KAP/Digital_UA_F      3.1 k271615 961104  o5r3so3  06-Mar-1997 14:49:02
      SUBROUTINE PKCUPARA_ ( MPPID, MPPNPR, TC1, KK1, IY1, W11, MN1 )
       AUTOMATIC K1
       INTEGER K1
       AUTOMATIC II5
       INTEGER II5
       INTEGER KK1
       INTEGER MPPID
       INTEGER*8 DI1(0:7,0:49)
       AUTOMATIC II3
       INTEGER II3
       AUTOMATIC I1
       INTEGER I1
       INTEGER II6(0:99)
       INTEGER MN1
       INTEGER II11
       PARAMETER (II11 = 10)
       AUTOMATIC II1
       INTEGER II1
       AUTOMATIC II4
       INTEGER II4
       INTEGER MPPNPR
       AUTOMATIC II2
       INTEGER II2
       DOUBLEPRECISION W11(MN1)
       INTEGER IY1(MN1)
       DOUBLEPRECISION W12(MN1)
       DOUBLEPRECISION TC1(MN1,KK1)
       INTEGER II12, II10, II9, II8, II7
       PARAMETER (II12 = 1, II10 = 2, II9 = 3, II8 = 4, II7 = 5)
       COMMON /mppfoi/II6
       COMMON /mppfod/DI1
       DI1(II6(II7),MPPID) = %LOC (MN1)
       DI1(II6(II8),MPPID) = %LOC (W11)
       DI1(II6(II9),MPPID) = %LOC (IY1)
       DI1(II6(II10),MPPID) = %LOC (KK1)
       DI1(II6(II12),MPPID) = %LOC (TC1)
C!!!! PARALLEL IF (KK .GT. 14) SHARED (KK,TC,IY,W1) LOCAL (K,I)
       II3 = KK1 - 1 + II12
       II4 = (II3 + MPPNPR - II12) / MPPNPR
       II1 = 1 + MPPID * II4
       II2 = MIN (KK1, II1 + (II4 - II12))
       DO II5=1,MN
        W12(II5) = W11(II5)
       END DO
C!!!! PDO FIRSTLOCAL (W1)
       DO K1=II1,II2
        DO I1=1,II11
         W12(I1) = TC1(I1,K1)
        END DO
        DO I1=1,II11
         TC1(I1,K1) = W12(IY1(I1))
        END DO
       END DO
C!!!! END PDO NOWAIT
C!!!! END PARALLEL 
      END
 
 
369.4This is being handled as an SPRHPCGRP::DEGREGORYKaren 223-5801Tue Apr 08 1997 14:100