Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
29341 Discussions

Integer value not be passed correctly between subroutines

d_latulipe
Novice
1,225 Views

The integer value "I_MONTH" is not being passed correctly between subroutine "Monthly_Ratings" and Subroutine "Calculate_Ratings". 

 

Cant figure out why.  Would this be a compiler problem?

 

Thank you.

 

SUBROUTINE MONTHLY_RATINGS
C************************************************************************
C
C SUBROUTINE: MONTHLY_RATINGS
C FUNCTION: CALCULATES MONTHLY RATINGS
C CALLS SUBROUTINE CALCULATE TO CALCULATE RATINGS FOR EACH MONTH
C REV 0: 05/24 DML
C
C************************************************************************
REAL LOADLOSS, LOSSMVA
REAL MAXOIL,MAXCU
CHARACTER*20 TXDATE,LIMITING,LIMITING_MONTHLY
DIMENSION PU(288)
INTEGER FIRST,OILHOUR,OILMINUTE,CUHOUR,CUMINUTE
INTEGER PEAKHOUR,PEAKMINUTE
INTEGER PEAKHOUR_MONTHLY,PEAKMINUTE_MONTHLY,OILHOUR_MONTHLY
INTEGER OILMINUTE_MONTHLY,CUHOUR_MONTHLY,CUMINUTE_MONTHLY
INTEGER POST_STE_SUM,POST_STE_WIN
CHARACTER*63 TITLE
CHARACTER*25 TYPE
CHARACTER*35 CONSTRUCTION
CHARACTER*20 RATING
REAL monthly_ambient_F

C * * * * * * * * * * * * * * COMMON BLOCK * * * * * * * * * * * * * * *
COMMON/INPUT/TITLE,CORELOSS,LOADLOSS,LOSSMVA,HRLOSS,LOSSCALC,
1 ITYPE,XN,XM,INSULATION,WCORE,WTANK,GALLONS,HRMVA,OILRISE,
1 AVECU,DELTA,MAXCU(4),MAXOIL(4),DURATION(4),OILCALC,
1 SUMMERCYCLE(24),WINTERCYCLE(24),PERCENT,REPORTSIZE,CUTAU,OILTAU,
1 XNAMEPLATE,monthly_ambient_F(14,2)

COMMON/OUTPUTS/HOTSPOT(4,288),PMAX(4),PMVA(4,288),
1 TOPOIL(4,288),LIMITING(4),HOTSPOTMAX(4),TOPOILMAX(4),
1 KJ,CONVERGENCE(4),SOLUTION(4),OILHOUR(4),OILMINUTE(4),
1 CUHOUR(4),CUMINUTE(4),PEAKHOUR(4),PEAKMINUTE(4),AMBIENT(4)

COMMON/MONTHLY/PMAX_MONTHLY(14,4),HOTSPOT_MONTHLY(14,4,288),
1 PMVA_MONTHLY(14,4,288),TOPOIL_MONTHLY(14,4,288),
1 LIMITING_MONTHLY(14,4),HOTSPOTMAX_MONTHLY(14,4),
1 TOPOILMAX_MONTHLY(14,4),OILHOUR_MONTHLY(14,4),
1 OILMINUTE_MONTHLY(14,4),CUHOUR_MONTHLY(14,4),
1 CUMINUTE_MONTHLY(14,4),PEAKHOUR_MONTHLY(14,4),
1 PEAKMINUTE_MONTHLY(14,4),I_MONTH

COMMON/CONSTANTS1/RATIO,TGFL,
1 FIRST(8),LAST(8),CONSTRUCTION,RATING(8)


COMMON/PUNIT/PUSUM(288),PUWIN(288),
1 NSUMMER,NWINTER

C * * * * * * * * * * * * * * COMMON BLOCK * * * * * * * * * * * * * * *

DO 110 I=1,14
I_MONTH = I 


AMBIENT(1) = (monthly_ambient_F(I,1)-32)/1.8 
AMBIENT(2) = (monthly_ambient_F(I,2)-32)/1.8
AMBIENT(3) = (monthly_ambient_F(I,2)-32)/1.8 
AMBIENT(4) = (monthly_ambient_F(I,2)-32)/1.8 

 

CALL CALCULATE_RATINGS 


DO 105 J=1,4
PMAX_MONTHLY(I,J)=PMAX(J)
PEAKHOUR_MONTHLY(I,J)=PEAKHOUR(J)
PEAKMINUTE_MONTHLY(I,J)=PEAKMINUTE(J)
TOPOILMAX_MONTHLY(I,J)=TOPOILMAX(J)
HOTSPOTMAX_MONTHLY(I,J)=HOTSPOTMAX(J)
OILHOUR_MONTHLY(I,J)=OILHOUR(J)
OILMINUTE_MONTHLY(I,J)=OILMINUTE(J)
CUHOUR_MONTHLY(I,J)=CUHOUR(J)
CUMINUTE_MONTHLY(I,J)=CUMINUTE(J)
LIMITING_MONTHLY(I,J)=LIMITING(J)

DO 100 K=1,288 
PMVA_MONTHLY(I,J,K)=PMVA(J,K)
TOPOIL_MONTHLY(I,J,K)=TOPOIL(J,K)
HOTSPOT_MONTHLY(I,J,K)=HOTSPOT(J,K)

100 CONTINUE
105 CONTINUE

110 CONTINUE

I_MONTH = 0 

RETURN
END

 

      SUBROUTINE CALCULATE_RATINGS
C************************************************************************
C
C    SUBROUTINE:  CALCULATE_RATINGS
C    FUNCTION:    CALCULATES RATINGS PER TEMPERATURE CRITERIA SPECIFIED.
C                 CALLS SUBROUTINE OILTEMP TO CALCULATE OIL TEMPERATURE 
C                 CALLS SUBROUTINE CUTEMP TO CALCUATE HOTSPOT TEMPERATURE
C    
C************************************************************************
      REAL LOADLOSS, LOSSMVA
      REAL MAXOIL,MAXCU
      CHARACTER*20 TXDATE,LIMITING
      DIMENSION PU(288)
      INTEGER FIRST,OILHOUR,OILMINUTE,CUHOUR,CUMINUTE
      INTEGER PEAKHOUR,PEAKMINUTE
      INTEGER POST_STE_SUM,POST_STE_WIN
      CHARACTER*63 TITLE
      CHARACTER*25 TYPE
      CHARACTER*35 CONSTRUCTION
      CHARACTER*20 RATING
      REAL monthly_ambient_F
C      INTEGER I_MONTH
 
C * * * * * * * * * * * * * * COMMON BLOCK * * * * * * * * * * * * * * *  
       COMMON/INPUT/TITLE,CORELOSS,LOADLOSS,LOSSMVA,HRLOSS,LOSSCALC,
     1 ITYPE,XN,XM,INSULATION,WCORE,WTANK,GALLONS,HRMVA,OILRISE,
     1 AVECU,DELTA,MAXCU(4),MAXOIL(4),DURATION(4),OILCALC,
     1 SUMMERCYCLE(24),WINTERCYCLE(24),PERCENT,REPORTSIZE,CUTAU,OILTAU,
     1 XNAMEPLATE,monthly_ambient_F(14,2)
 
       COMMON/OUTPUTS/HOTSPOT(4,288),PMAX(4),PMVA(4,288),
     1 TOPOIL(4,288),LIMITING(4),HOTSPOTMAX(4),TOPOILMAX(4),
     1 KJ,CONVERGENCE(4),SOLUTION(4),OILHOUR(4),OILMINUTE(4),
     1 CUHOUR(4),CUMINUTE(4),PEAKHOUR(4),PEAKMINUTE(4),AMBIENT(4)
 
        COMMON/MONTHLY/PMAX_MONTHLY(14,4),HOTSPOT_MONTHLY(14,4,288),
     1  PMVA_MONTHLY(14,4,288),TOPOIL_MONTHLY(14,4,288),
     1  LIMITING_MONTHLY(14,4),HOTSPOTMAX_MONTHLY(14,4),
     1  TOPOILMAX_MONTHLY(14,4),OILHOUR_MONTHLY(14,4),
     1  OILMINUTE_MONTHLY(14,4),CUHOUR_MONTHLY(14,4),
     1  CUMINUTE_MONTHLY(14,4),PEAKHOUR_MONTHLY(14,4),
     1  PEAKMINUTE_MONTHLY(14,4),I_MONTH
 
      
        COMMON/AMBIENTS/PMAX_AMBIENT(30,4),HOTSPOT_AMBIENT(30,4,288),
     1  PMVA_AMBIENT(30,4,288),TOPOIL_AMBIENT(30,4,288),
     1  LIMITING_AMBIENT(30,4),HOTSPOTMAX_AMBIENT(30,4),
     1  TOPOILMAX_AMBIENT(30,4),OILHOUR_AMBIENT(30,4),
     1  OILMINUTE_AMBIENT(30,4),CUHOUR_AMBIENT(30,4),
     1  CUMINUTE_AMBIENT(30,4),PEAKHOUR_AMBIENT(30,4),
     1  PEAKMINUTE_AMBIENT(30,4),AMBIENT_F(30), AMBIENT_C(30),M
       
       COMMON/CONSTANTS1/RATIO,TGFL,
     1 FIRST(8),LAST(8),CONSTRUCTION,RATING(8)
 
 
       COMMON/PUNIT/PUSUM(288),PUWIN(288),
     1 NSUMMER,NWINTER
 
C * * * * * * * * * * * * * * COMMON BLOCK * * * * * * * * * * * * * * *  
 
 
       DO 265 KJ=1,4 !calculate 4 different ratings: normal, LTE, STE & DAL
 
 
        IF (I_MONTH .GT. 0)THEN  
         DO 120 I=1,288          
             IF(I_MONTH.LT.4 .OR. I_MONTH .GT. 9)THEN
                PU(I)=PUWIN(I)
             ELSE
                PU(I)=PUSUM(I)  
             ENDIF
 120     CONTINUE
 
 
         
         
        ELSE                       RATINGS
         DO 121 I=1,288          
             IF(M.LT. 51)THEN 
                PU(I)=PUWIN(I)
             ELSE
                PU(I)=PUSUM(I)   
             ENDIF
 121     CONTINUE
        ENDIF
 
 
 
      
      PMAX(KJ)=2*XNAMEPLATE 
 125  STEP=PMAX(KJ)*(-0.25) 
      ILASTOVER=.TRUE. 
      MOILSTEPS=0
      MCUSTEPS=0
     
      DO 200 IK=1,50  
 
       DO 130 I=1,288     
       IF(I.LE.FIRST(KJ).OR.I.GT.LAST(KJ))THEN
       PMVA(KJ,I)=    PU(I)*PRELOAD 
       ELSE
       PMVA(KJ,I) =   PU(I)*PMAX(KJ)
       ENDIF
 
 
 
       IF(KJ.EQ.3.AND.I.GT.LAST(3).AND.I.LT.POST_STE_SUM)THEN  
       PMVA(3,I) =   PU(I)*POSTLOAD
       ENDIF
 130  CONTINUE 
      
      CALL OILTEMP(IOILSTEPS)     
      IF (IOILSTEPS .GT. MOILSTEPS) MOILSTEPS = IOILSTEPS
 
 
 170  CONTINUE
       CALL CUTEMP(ICUSTEPS)   
      IF (ICUSTEPS .GT. MCUSTEPS) MCUSTEPS = ICUSTEPS 
 
      IOVERLOAD=.FALSE.     !
 
      DO 190 I=1,288
        IF (TOPOIL(KJ,I)  .GT. MAXOIL(KJ)) THEN
          IOVERLOAD = .TRUE.
          LIMITING(KJ)='TOP-OIL'
        ENDIF
        IF(HOTSPOT(KJ,I) .GT. MAXCU(KJ)) THEN
           IOVERLOAD = .TRUE.
           LIMITING(KJ)='HOT-SPOT'
           LIMITING(KJ)='HOT-SPOT'
        ENDIF
 190  CONTINUE
 
 
  
      IF((.NOT. IOVERLOAD) .AND. IK .EQ. 1) THEN 
          LIMITING(KJ)='TWICE-NAMEPLATE MVA' 
         GOTO 240
      ELSEIF((.NOT. IOVERLOAD) .AND. ILASTOVER) THEN
          IF(ABS(STEP) .LT. (PMAX(KJ)*0.001)) GOTO 230 !
          STEP=STEP*(-0.33) 
      ENDIF
      IF((.NOT. ILASTOVER) .AND. IOVERLOAD) THEN
          STEP=STEP*(-0.33) 
      ENDIF
 
      ILASTOVER=IOVERLOAD 
      PMAX(KJ)=PMAX(KJ)+STEP 
       
      IF(PMAX(KJ).LT.-0.001) THEN          
          SOLUTION(KJ)=1       
          WRITE(7,495)!report convergence info to fort.7
 495      FORMAT('NO SOLUTION',//)
          GOTO 230
      ENDIF
 
 200  CONTINUE
       
 230     IF ( (IK .GE. 50) .OR. (MOILSTEPS .GE. 20) .OR. 
     1     (MCUSTEPS .GE. 20) ) THEN
          CONVERGENCE(KJ)=1
          WRITE (7,*)  ' <<<<<<<<<<< NO CONVERGENCE >>>>>>>>>>>>>>'  !writes convergence info to fort.7
      ELSEIF (PMAX(KJ).LT.-0.001) THEN
           GOTO 265 
      ENDIF
 
          TOPOILMAX(KJ)=0.0 
          HOTSPOTMAX(KJ)=0.0           
 
 240      DO 245 I=1,288
          IF(TOPOIL(KJ,I).GT.TOPOILMAX(KJ))THEN 
            TOPOILMAX(KJ)=TOPOIL(KJ,I) 
            OILINDEX=I            
          ENDIF  
          IF(HOTSPOT(KJ,I).GT.HOTSPOTMAX(KJ))THEN  
            HOTSPOTMAX(KJ)=HOTSPOT(KJ,I)
            CUINDEX=I            
          ENDIF
 245   CONTINUE
 
        OILHOUR(KJ)=INT((OILINDEX-1)/12.)+1.0          
        OILMINUTE(KJ)= NINT(((OILINDEX-1.)/12. - OILHOUR(KJ)+1.)*60)
        CUHOUR(KJ)=INT((CUINDEX-1.)/12.)+1.0
        CUMINUTE(KJ)= NINT(((CUINDEX-1.)/12. - CUHOUR(KJ)+1.)*60)
 
       HIGHEST=0.0      !find interval at which load is max 
       DO 250  I=1,288
       IF (PMVA(KJ,I).GT.HIGHEST)THEN
         HIGHEST = PMVA(KJ,I)
         PMAX(KJ) = HIGHEST
         PEAKINDEX=I
         ENDIF
 250   CONTINUE
 
        PEAKHOUR(KJ)=INT((PEAKINDEX-1.)/12.)+1.0 !find hour and minute at which load is max
        PEAKMINUTE(KJ)=NINT(((PEAKINDEX-1.)/12.- PEAKHOUR(KJ)+1.)*60)
 
      IF (KJ.EQ.1.OR.KJ.EQ.5) THEN!define preload value for all emergency ratings
      PRELOAD=PMAX(KJ)*PERCENT/100   !preload = some % of the normal rating
      ENDIF
 
      IF (KJ.EQ.2.OR.KJ.EQ.6) THEN!define preload value for STE ratings
      POSTLOAD=PMAX(KJ)   !postload = LTE RATING
      ENDIF
 
      IF(ITYPE.EQ.2) THEN            !multiply ratings by 3 if 3-single phase xfmrs
       PMAX(KJ) = 3.0*PMAX(KJ)  
       DO 255  I=1,288
        PMVA(KJ,I)=PMVA(KJ,I)*3.0
 255  CONTINUE
      ENDIF
      
 265   CONTINUE
       
 
      RETURN
      END

 

 

 

 

 

 

0 Kudos
8 Replies
jimdempseyatthecove
Honored Contributor III
1,153 Views

Windows instruction using Microsoft Visual Studio.

prior to call insert a diagnostic

print *,"location of I_MONTH", LOC(I_MONTH)

 

Inside the called subroutine

insert the same line.

 

At runtime, expect the same location to be displayed. If it does not, something is wrong.

As you have not pasted the code properly, we cannot tell the character spacing.

To insert code properly, click on the ...'s to increase the list of options in the edit window.

Then click on the </>, button, click on the Markup button, a pull-down list is shown, Select Fortran, then paste your code in the edit window. Then exit the edit window.

 

The named common block /MONTHLY/ looks OK in both subroutines.

Assuming the addresses of I_MONTH are the same, then

 

In the caller procedure, before the call, examine the value of I_MONTH, and verify that it is what you expect.

Then, in the bottom of MS VS (where the Watch tab is located), you will see a tab for Breakpoints. If it is not there, at the top click

Debug | Windows | Breakpoints

click on the Breakpoints tab

In there, clicks: New | Data Breakpoint

in the location insert: loc(I_MONTH)

 

Then continue to a breakpoint in the second procedure where you observe the incorrect value for i_month

Note, if something alters the caller's I_MONTH you will have a break at that statement.

This may show you an array being indexed out of bounds.

 

Jim Dempsey

d_latulipe
Novice
1,140 Views

Thank  you Jim

 

I attached my code.   In the meantime, I will try the "diagnostic print *,"location of I_MONTH", LOC(I_MONTH)" that you recommended.

 

 

0 Kudos
andrew_4619
Honored Contributor III
1,111 Views

well for 20 minutes of fun I downloaded your program and put it in an IFX project in vs2022. I compiles OK. I found some input data in a comment so I copies to a file and put a line to open that as unit 5 (var G) in the read routine.

 

Anyway in the debugger in "Monthly_Ratings" it cycles through values 1 to 14 and in Subroutine "Calculate_Ratings" we get 1 to 14.

It then calls "Calculate_Ratings" from some other place with I_MONTH set to zero..... I stopped at that point.

 

I do no see the problem you describe, the common block with I_MONTH all check as consistent.

 

 

d_latulipe
Novice
1,095 Views

ok. thanks Andrew

 

When I run the program (look at fort.7 output file),  I see I_Month being incremented from 1 to 14 in Monthly_Ratings subroutine, but after passing it to Calculate_Ratings subroutine, I_Month is increases directly from 0 to 19, with no increments in between.

 

I am using intel fortran compiler 17.0, and VS 2019.

 

 

 

0 Kudos
andrew_4619
Honored Contributor III
1,069 Views

interesting 

andrew_4619_0-1733875773197.png

 

The hover in the debugger shows I_MONTH = 1 the print to console shows 0. Something is screwed.....

 

I changed the print to show the address also and had the same print before the call....

andrew_4619_1-1733876121592.png

You can clearly see that memory address is different !!!!!!!!!!!!!! Something is broken.

0 Kudos
andrew_4619
Honored Contributor III
1,061 Views

Your problem is  CHARACTER*20 TXDATE,LIMITING,LIMITING_MONTHLY

LIMITING_MONTHLY is an array in a common BUT is not declared in all locations so at some places is is an array of char 20 and in others it is an array of integer.  The memory locations then get foo bahed as a result. If you declared everything and used implicit none it would have been caught.  The best quick fix is to declare all the common variables in a module and just use that module in all the places a common is used,

d_latulipe
Novice
991 Views

Thanks Andrew

 

Strange. I thought that I only had to declare the variable in a subroutine if I actually used it in that subroutine.  Anyway.  I declared them all in each subroutine. 

0 Kudos
andrew_4619
Honored Contributor III
980 Views

Everything should be declared everywhere as a matter of principle. This is a small program it would not take long.

1] Using implicit typing (assumed type based on the initial letter) is fraught with problems, it is so easy to get it wrong, for example misspelling a variable does not get picked up.

2] Commons are tedious and very obsolete, you must have everything matching everywhere. Putting the common declarations in an include file and including it where used is a fix for that as you can't have mismatches then and adding something adds in one place only, so much easier.

But I get that maybe  people are not comfortable changing a way of working, if it 'works'. A solution using a data module would be the best 'easy' fix IMO.

Anyway problem solved for now.....

 

Reply