diff --git a/fortran/wrf_cloud_fracf.f90 b/fortran/wrf_cloud_fracf.f90 index f3b23ea..61cbe4c 100644 --- a/fortran/wrf_cloud_fracf.f90 +++ b/fortran/wrf_cloud_fracf.f90 @@ -29,11 +29,11 @@ SUBROUTINE DCLOUDFRAC(pres, rh, lowc, midc, highc, nz, ns, ew) DO k = 1,nz-1 IF (k .GE. kclo .AND. k .LT. kcmi) THEN - lowc(i,j) = AMAX1(rh(i,j,k), lowc(i,j)) + lowc(i,j) = MAX(rh(i,j,k), lowc(i,j)) ELSE IF (k .GE. kcmi .AND. k .LT. kchi) THEN ! mid cloud - midc(i,j) = AMAX1(rh(i,j,k), midc(i,j)) + midc(i,j) = MAX(rh(i,j,k), midc(i,j)) ELSE if (k .GE. kchi) THEN ! high cloud - highc(i,j) = AMAX1(rh(i,j,k), highc(i,j)) + highc(i,j) = MAX(rh(i,j,k), highc(i,j)) END IF END DO @@ -41,12 +41,12 @@ SUBROUTINE DCLOUDFRAC(pres, rh, lowc, midc, highc, nz, ns, ew) midc(i,j) = 4.0*midc(i,j)/100. - 3.0 highc(i,j) = 2.5*highc(i,j)/100. - 1.5 - lowc(i,j) = amin1(lowc(i,j), 1.0) - lowc(i,j) = amax1(lowc(i,j), 0.0) - midc(i,j) = amin1(midc(i,j), 1.0) - midc(i,j) = amax1(midc(i,j), 0.0) - highc(i,j) = amin1(highc(i,j), 1.0) - highc(i,j) = amax1(highc(i,j), 0.0) + lowc(i,j) = MIN(lowc(i,j), 1.0) + lowc(i,j) = MAX(lowc(i,j), 0.0) + midc(i,j) = MIN(midc(i,j), 1.0) + midc(i,j) = MAX(midc(i,j), 0.0) + highc(i,j) = MIN(highc(i,j), 1.0) + highc(i,j) = MAX(highc(i,j), 0.0) END DO END DO diff --git a/fortran/wrf_rip_phys_routines.f90 b/fortran/wrf_rip_phys_routines.f90 index ed40d5e..328866b 100644 --- a/fortran/wrf_rip_phys_routines.f90 +++ b/fortran/wrf_rip_phys_routines.f90 @@ -70,7 +70,7 @@ SUBROUTINE WETBULBCALC(prs, tmk, qvp, twb, nx, ny, nz, psafile, errstat, errmsg) DO k=1,nz DO j=1,ny DO i=1,nx - q = DMAX1(qvp(i,j,k), 1.D-15) + q = MAX(qvp(i,j,k), 1.D-15) t = tmk(i,j,k) p = prs(i,j,k)/100. e = q*p/(EPS + q) diff --git a/fortran/wrf_user.f90 b/fortran/wrf_user.f90 index cee1632..3d92b4f 100644 --- a/fortran/wrf_user.f90 +++ b/fortran/wrf_user.f90 @@ -608,9 +608,9 @@ SUBROUTINE DCOMPUTERH(qv, p, t, rh, nx) es = EZERO*EXP(ESLCON1*(temperature - CELKEL)/(temperature - ESLCON2)) ! qvs = ep_2*es/(pressure-es) qvs = EPS*es/(0.01D0*pressure - (1.D0 - EPS)*es) - ! rh = 100*amax1(1., qv(i)/qvs) + ! rh = 100*MAX(1., qv(i)/qvs) ! rh(i) = 100.*qv(i)/qvs - rh(i) = 100.D0*DMAX1(DMIN1(qv(i)/qvs, 1.0D0), 0.0D0) + rh(i) = 100.D0*MAX(MIN(qv(i)/qvs, 1.0D0), 0.0D0) END DO RETURN @@ -645,7 +645,7 @@ SUBROUTINE DGETIJLATLONG(lat_array, long_array, lat, longitude, ii, jj, nx, ny, DO i = 1,nx latd = (lat_array(i,j) - lat)**2 longd = (long_array(i,j) - longitude)**2 - ! longd = dmin1((long_array(i,j)-longitude)**2, & + ! longd = MIN((long_array(i,j)-longitude)**2, & ! (long_array(i,j)+longitude)**2) dist = SQRT(latd + longd) IF (dist_min .GT. dist) THEN @@ -792,12 +792,12 @@ SUBROUTINE DCOMPUTETD(td, pressure, qv_in, nx) INTEGER :: i DO i = 1,nx - qv = DMAX1(qv_in(i), 0.D0) + qv = MAX(qv_in(i), 0.D0) ! vapor pressure tdc = qv*pressure(i)/(.622D0 + qv) ! avoid problems near zero - tdc = DMAX1(tdc, 0.001D0) + tdc = MAX(tdc, 0.001D0) td(i) = (243.5D0*LOG(tdc) - 440.8D0)/(19.48D0 - LOG(tdc)) END DO @@ -834,7 +834,7 @@ SUBROUTINE DCOMPUTEICLW(iclw, pressure, qc_in, nx, ny, nz) DO j = 3,ny - 2 DO i = 3,nx - 2 DO k = 1,nz - qclw = DMAX1(qc_in(i,j,k), 0.D0) + qclw = MAX(qc_in(i,j,k), 0.D0) IF (k.EQ.1) THEN dp = pressure(i,j,k-1) - pressure(i,j,k) ELSE IF (k.EQ.nz) then diff --git a/fortran/wrf_user_dbz.f90 b/fortran/wrf_user_dbz.f90 index 0ff3470..d1151f0 100644 --- a/fortran/wrf_user_dbz.f90 +++ b/fortran/wrf_user_dbz.f90 @@ -136,8 +136,8 @@ SUBROUTINE CALCDBZ(prs, tmk, qvp, qra, qsn, qgr, sn0, ivarint, iliqskin, dbz, nx ! Calculate variable intercept parameters IF (ivarint .EQ. 1) THEN - temp_c = DMIN1(-0.001D0, tmk(i,j,k)-CELKEL) - sonv = DMIN1(2.0D8, 2.0D6*EXP(-0.12D0*temp_c)) + temp_c = MIN(-0.001D0, tmk(i,j,k)-CELKEL) + sonv = MIN(2.0D8, 2.0D6*EXP(-0.12D0*temp_c)) gonv = gon IF (qgr(i,j,k) .GT. R1) THEN