Skip to content
This repository has been archived by the owner on Nov 8, 2024. It is now read-only.

Commit

Permalink
Fortran syntax errors, phys dir, from Cray (#203)
Browse files Browse the repository at this point in the history
TYPE: bug fix

KEYWORDS: Cray, physics, syntax, Fortran

SOURCE: Pete Johnsen (Cray, Inc.)

DESCRIPTION OF CHANGES:

Compilation errors due to syntax problems found with Cray compilers.

Problem (Fortran 2003 Bible: section 7.1.2, p 205, "(A+B) * -2 ! Invalid syntax"

   a = b * -c
Fix

   a = b * (-1.0) * c
Problem

   write (*,*), a
Fix

   write (*,*)  a
Problem

   write (6,'("string 1" &
              "string 2" )' )
Fix

   write (6,'("string 1" &
             &"string 2" )' )
Problem

    a = b + c + &
              + d
Fix

    a = b + c   &
              + d
LIST OF MODIFIED FILES:

M phys/module_bl_mynn.F
M phys/module_diag_rasm.F
M phys/module_mp_morr_two_moment.F
M phys/module_ra_rrtmg_swf.F

TESTS CONDUCTED:

 Reggie 3.07: passed
  • Loading branch information
davegill committed Mar 24, 2017
1 parent 456c640 commit cb97bce
Show file tree
Hide file tree
Showing 4 changed files with 21 additions and 21 deletions.
2 changes: 1 addition & 1 deletion phys/module_bl_mynn.F
Original file line number Diff line number Diff line change
Expand Up @@ -3107,7 +3107,7 @@ SUBROUTINE mynn_mix_chem(kts,kte, &
b(1)=1.+dtz(k)*dfh(k+1)
c(1)=-dtz(k)*dfh(k+1)
! d(1)=sqv(k) + dtz(k)*flqv + qcd(k)*delt
d(1)=chem1(k,ic) + dtz(k) * -vd1(ic)*chem1(1,ic)
d(1)=chem1(k,ic) + dtz(k) * (-1.0) * vd1(ic) * chem1(1,ic)
DO k=kts+1,kte-1
kk=k-kts+1
Expand Down
28 changes: 14 additions & 14 deletions phys/module_diag_rasm.F
Original file line number Diff line number Diff line change
Expand Up @@ -1006,11 +1006,11 @@ SUBROUTINE getAvgState(currentTime, xtime, dt, mean_interval, output_freq, compu
nextTime = currentTime + off
call WRFU_TimeGet( nextTime, yy=yr, mm=mon, dd=day, h=hr, m=min, s=sec)

WRITE(str_yr, '(I4.4)'), yr
WRITE(str_mon, '(I2.2)'), mon
WRITE(str_day, '(I2.2)'), day
WRITE(str_yr, '(I4.4)') yr
WRITE(str_mon, '(I2.2)') mon
WRITE(str_day, '(I2.2)') day
totalsec = (hr * 60 * 60) + (min * 60) + sec
WRITE(str_sec, '(I5.5)'), totalsec
WRITE(str_sec, '(I5.5)') totalsec
filedate = trim(str_yr)//"-"//trim(str_mon)//"-"//trim(str_day)//"-"//trim(str_sec)
OutDateStr = filedate

Expand All @@ -1028,8 +1028,8 @@ SUBROUTINE getAvgState(currentTime, xtime, dt, mean_interval, output_freq, compu
ELSE
mon = mon - 1
ENDIF
WRITE(str_yr, '(I4.4)'), yr
WRITE(str_mon, '(I2.2)'), mon
WRITE(str_yr, '(I4.4)') yr
WRITE(str_mon, '(I2.2)') mon
filedate = trim(str_yr)//"-"//trim(str_mon)
OutDateStr = filedate

Expand All @@ -1041,9 +1041,9 @@ SUBROUTINE getAvgState(currentTime, xtime, dt, mean_interval, output_freq, compu
call WRFU_TimeIntervalSet( off, s=mean_interval-dtime)
prevTime = currentTime - off
call WRFU_TimeGet( prevTime, yy=yr, mm=mon, dd=day)
WRITE(str_yr, '(I4.4)'), yr
WRITE(str_mon, '(I2.2)'), mon
WRITE(str_day, '(I2.2)'), day
WRITE(str_yr, '(I4.4)') yr
WRITE(str_mon, '(I2.2)') mon
WRITE(str_day, '(I2.2)') day
filedate = trim(str_yr)//"-"//trim(str_mon)//"-"//trim(str_day)
OutDateStr = filedate

Expand Down Expand Up @@ -1143,8 +1143,8 @@ SUBROUTINE getDiurnalState(currentTime, xtime, dt, diurn_interval, output_freq,
ELSE
mon = mon - 1
ENDIF
WRITE(str_yr, '(I4.4)'), yr
WRITE(str_mon, '(I2.2)'), mon
WRITE(str_yr, '(I4.4)') yr
WRITE(str_mon, '(I2.2)') mon
filedate = trim(str_yr)//"-"//trim(str_mon)
OutDateStr = filedate

Expand All @@ -1155,9 +1155,9 @@ SUBROUTINE getDiurnalState(currentTime, xtime, dt, diurn_interval, output_freq,
call WRFU_TimeIntervalSet( off, s=diurn_interval-dtime)
prevTime = currentTime - off
call WRFU_TimeGet( prevTime, yy=yr, mm=mon, dd=day)
WRITE(str_yr, '(I4.4)'), yr
WRITE(str_mon, '(I2.2)'), mon
WRITE(str_day, '(I2.2)'), day
WRITE(str_yr, '(I4.4)') yr
WRITE(str_mon, '(I2.2)') mon
WRITE(str_day, '(I2.2)') day
filedate = trim(str_yr)//"-"//trim(str_mon)//"-"//trim(str_day)
OutDateStr = filedate

Expand Down
2 changes: 1 addition & 1 deletion phys/module_mp_morr_two_moment.F
Original file line number Diff line number Diff line change
Expand Up @@ -3298,7 +3298,7 @@ SUBROUTINE MORR_TWO_MOMENT_MICRO(QC3DTEN,QI3DTEN,QNI3DTEN,QR3DTEN, &
#if (WRF_CHEM == 1)
evapprod(k) = - PRE(K) - EPRDS(K) - EPRDG(K)
rainprod(k) = PRA(K) + PRC(K) + PSACWS(K) + PSACWG(K) + PGSACW(K) &
+ PRAI(K) + PRCI(K) + PRACI(K) + PRACIS(K) + &
+ PRAI(K) + PRCI(K) + PRACI(K) + PRACIS(K) &
+ PRDS(K) + PRDG(K)
#endif
Expand Down
10 changes: 5 additions & 5 deletions phys/module_ra_rrtmg_swf.F
Original file line number Diff line number Diff line change
Expand Up @@ -12305,16 +12305,16 @@ SUBROUTINE RRTMG_SWRAD_FAST( &
end do
if( slope < 0. ) then
write(msg,'("ERROR: Negative total optical depth of ",f8.2,&
" at point i,j,nb=",3i5)') slope,i,j,nb
& " at point i,j,nb=",3i5)') slope,i,j,nb
call wrf_error_fatal(msg)
else if( slope > 6. ) then
call wrf_message("-------------------------")
write(msg,'("WARNING: Large total sw optical depth of ",f8.2,&
" at point i,j,nb=",3i5)') slope,i,j,nb
& " at point i,j,nb=",3i5)') slope,i,j,nb
call wrf_message(msg)

call wrf_message("Diagnostics 1: k, tauaer300, tauaer400,&
tauaer600, tauaer999, tauaer")
& tauaer600, tauaer999, tauaer")
do k=kts,kte
write(msg,'(i4,5f8.2)') k, tauaer300(i,k,j), tauaer400(i,k,j), &
tauaer600(i,k,j), tauaer999(i,k,j),tauaer(icol,k,nb)
Expand All @@ -12325,15 +12325,15 @@ SUBROUTINE RRTMG_SWRAD_FAST( &
end do

call wrf_message("Diagnostics 2: k, gaer300, gaer400, gaer600,&
gaer999")
& gaer999")
do k=kts,kte
write(msg,'(i4,4f8.2)') k, gaer300(i,k,j), gaer400(i,k,j), &
gaer600(i,k,j), gaer999(i,k,j)
call wrf_message(msg)
end do

call wrf_message("Diagnostics 3: k, waer300, waer400, waer600,&
waer999")
& waer999")
do k=kts,kte
write(msg,'(i4,4f8.2)') k, waer300(i,k,j), waer400(i,k,j), &
waer600(i,k,j), waer999(i,k,j)
Expand Down

0 comments on commit cb97bce

Please sign in to comment.