Skip to content

Commit

Permalink
Merge pull request #106 from PhilMiller/PhilMiller/negation
Browse files Browse the repository at this point in the history
Avoid relying on non-standard Fortran syntax extension for unary negation
  • Loading branch information
GreyREvenson committed May 22, 2024
2 parents 4b1e899 + c8adfae commit 5be0faa
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 15 deletions.
4 changes: 2 additions & 2 deletions src/AtmProcessing.f90
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,7 @@ SUBROUTINE ATM (options, parameters, forcing, energy, water)
! Used in opt_snf 6 and 7
IF(options%OPT_SNF == 6 .or. options%OPT_SNF == 7) THEN
rh = 0.263 * forcing%SFCPRS * forcing%Q2 * &
((exp((17.67 * (forcing%SFCTMP - 273.15)) / (forcing%SFCTMP - 29.65)))**-1)
((exp((17.67 * (forcing%SFCTMP - 273.15)) / (forcing%SFCTMP - 29.65)))**(-1))
rh = min(rh, 100.0) ! in case estimated rh > 100
ENDIF

Expand Down Expand Up @@ -211,4 +211,4 @@ SUBROUTINE ATM (options, parameters, forcing, energy, water)

END SUBROUTINE ATM

end module AtmProcessing
end module AtmProcessing
26 changes: 13 additions & 13 deletions src/SurfaceRunoffInfiltration.f90
Original file line number Diff line number Diff line change
Expand Up @@ -129,8 +129,8 @@ SUBROUTINE COMPUTE_VIC_SURFRUNOFF(parameters,domain,levels,water)
water%ASAT = 0.0

DO IZ=1,levels%nsoil-2
TOP_MOIST = TOP_MOIST + (water%SMC(IZ) * -1 * domain%ZSOIL(IZ)) ! m
TOP_MAX_MOIST = TOP_MAX_MOIST + (parameters%SMCMAX(IZ)*-1*domain%ZSOIL(IZ)) ! m
TOP_MOIST = TOP_MOIST + (water%SMC(IZ) * (-1) * domain%ZSOIL(IZ)) ! m
TOP_MAX_MOIST = TOP_MAX_MOIST + (parameters%SMCMAX(IZ)*(-1)*domain%ZSOIL(IZ)) ! m
END DO

! Saturated area from soil moisture
Expand Down Expand Up @@ -197,13 +197,13 @@ SUBROUTINE COMPUTE_XAJ_SURFRUNOFF(parameters,domain,levels,water)

DO IZ=1,levels%nsoil-2
IF ((water%SMC(IZ)-parameters%SMCREF(IZ)) .GT. 0.) THEN ! soil moisture greater than field capacity
SM = SM + (water%SMC(IZ) - parameters%SMCREF(IZ) )*-1*domain%ZSOIL(IZ) !m
WM = WM + (parameters%SMCREF(IZ)*-1*domain%ZSOIL(IZ)) !m
SM = SM + (water%SMC(IZ) - parameters%SMCREF(IZ) )*(-1)*domain%ZSOIL(IZ) !m
WM = WM + (parameters%SMCREF(IZ)*(-1)*domain%ZSOIL(IZ)) !m
ELSE
WM = WM + (water%SMC(IZ)*-1*domain%ZSOIL(IZ))
WM = WM + (water%SMC(IZ)*(-1)*domain%ZSOIL(IZ))
END IF
WM_MAX = WM_MAX + (parameters%SMCREF(IZ)*-1*domain%ZSOIL(IZ))
SM_MAX = SM_MAX + (parameters%SMCMAX(IZ) - parameters%SMCREF(IZ))*-1*domain%ZSOIL(IZ)
WM_MAX = WM_MAX + (parameters%SMCREF(IZ)*(-1)*domain%ZSOIL(IZ))
SM_MAX = SM_MAX + (parameters%SMCMAX(IZ) - parameters%SMCREF(IZ))*(-1)*domain%ZSOIL(IZ)
END DO
WM = MIN(WM,WM_MAX) ! tension water (m)
SM = MIN(SM,SM_MAX) ! free water (m)
Expand Down Expand Up @@ -286,8 +286,8 @@ SUBROUTINE DYNAMIC_VIC(parameters,options,domain,levels,water)
BB = parameters%BBVIC

DO IZ=1,levels%nsoil-2
TOP_MOIST = TOP_MOIST + (water%SMC(IZ)*-1*domain%ZSOIL(IZ)) ! actual moisture in top layers, [m]
TOP_MAX_MOIST = TOP_MAX_MOIST + (parameters%SMCMAX(IZ)*-1*domain%ZSOIL(IZ)) ! maximum moisture in top layers, [m]
TOP_MOIST = TOP_MOIST + (water%SMC(IZ)*(-1)*domain%ZSOIL(IZ)) ! actual moisture in top layers, [m]
TOP_MAX_MOIST = TOP_MAX_MOIST + (parameters%SMCMAX(IZ)*(-1)*domain%ZSOIL(IZ)) ! maximum moisture in top layers, [m]
END DO
IF(TOP_MOIST .GT. TOP_MAX_MOIST) TOP_MOIST = TOP_MAX_MOIST
DP = water%QINSUR * DT ! precipitation depth, [m]
Expand Down Expand Up @@ -566,7 +566,7 @@ SUBROUTINE SMITH_PARLANGE_INFIL(parameters,domain,levels,water,FSUR,INFLMAX)
! estimate initial soil hydraulic conductivty (Ki in the equation), WCND (m/s)
CALL WDFCND2 (parameters,WDF,WCND,parameters%SMCWLT(ISOIL),0.0,ISOIL)
! Maximum infiltrability based on the Eq. 6.25. (m/s)
JJ = parameters%G * (parameters%SMCMAX(ISOIL) - parameters%SMCWLT(ISOIL)) * -1 * domain%ZSOIL(ISOIL)
JJ = parameters%G * (parameters%SMCMAX(ISOIL) - parameters%SMCWLT(ISOIL)) * (-1) * domain%ZSOIL(ISOIL)
FSUR = parameters%DKSAT(ISOIL) + (GAM * (parameters%DKSAT(ISOIL) - WCND) / (EXP(GAM * 1E-05 / JJ) -1))
! infiltration rate at surface
IF(parameters%DKSAT(ISOIL) .LT. water%QINSUR)THEN
Expand All @@ -579,7 +579,7 @@ SUBROUTINE SMITH_PARLANGE_INFIL(parameters,domain,levels,water,FSUR,INFLMAX)
! estimate initial soil hydraulic conductivty (Ki in the equation), WCND (m/s)
CALL WDFCND2 (parameters,WDF,WCND,water%SMC(ISOIL),water%SICE(ISOIL),ISOIL)
! Maximum infiltrability based on the Eq. 6.25. (m/s)
JJ = parameters%G * (parameters%SMCMAX(ISOIL) - water%SMC(ISOIL)) * -1 * domain%ZSOIL(ISOIL)
JJ = parameters%G * (parameters%SMCMAX(ISOIL) - water%SMC(ISOIL)) * (-1) * domain%ZSOIL(ISOIL)
FSUR = parameters%DKSAT(ISOIL) + (GAM * (parameters%DKSAT(ISOIL) - WCND)/(EXP(GAM*water%FACC/JJ)-1))
! infiltration rate at surface
IF(parameters%DKSAT(ISOIL) .LT. water%QINSUR)THEN
Expand Down Expand Up @@ -623,15 +623,15 @@ SUBROUTINE GREEN_AMPT_INFIL(parameters,domain,levels,water,FSUR,INFLMAX)
! estimate initial soil hydraulic conductivty (Ki in the equation), WCND (m/s)
CALL WDFCND2 (parameters,WDF,WCND,parameters%SMCWLT(ISOIL),0.0,ISOIL)
! Maximum infiltrability based on the Eq. 6.25. (m/s)
JJ = parameters%G*(parameters%SMCMAX(ISOIL)-parameters%SMCWLT(ISOIL))*-1*domain%ZSOIL(ISOIL)
JJ = parameters%G*(parameters%SMCMAX(ISOIL)-parameters%SMCWLT(ISOIL))*(-1)*domain%ZSOIL(ISOIL)
FSUR = parameters%DKSAT(ISOIL) + ((JJ/1E-05) * (parameters%DKSAT(ISOIL) - WCND))
!maximum infiltration rate at surface
IF(FSUR .LT. 0.0) FSUR = 0.0
ELSE
! estimate initial soil hydraulic conductivty (Ki in the equation), WCND (m/s)
CALL WDFCND2 (parameters,WDF,WCND,water%SMC(ISOIL),water%SICE(ISOIL),ISOIL)
! Maximum infiltrability based on the Eq. 6.25. (m/s)
JJ = parameters%G * (parameters%SMCMAX(ISOIL) - water%SMC(ISOIL))*-1*domain%ZSOIL(ISOIL)
JJ = parameters%G * (parameters%SMCMAX(ISOIL) - water%SMC(ISOIL))*(-1)*domain%ZSOIL(ISOIL)
FSUR = parameters%DKSAT(ISOIL) + ((JJ/water%FACC) * (parameters%DKSAT(ISOIL) - WCND))
! infiltration rate at surface
IF(parameters%DKSAT(ISOIL) .LT. water%QINSUR)THEN
Expand Down

0 comments on commit 5be0faa

Please sign in to comment.