Skip to content

Commit

Permalink
Merge pull request #139 from MengZhang/develop_PM
Browse files Browse the repository at this point in the history
Develop pm update
  • Loading branch information
chporter committed Aug 12, 2021
2 parents 1385217 + b81a77e commit 44053ea
Show file tree
Hide file tree
Showing 7 changed files with 47 additions and 47 deletions.
24 changes: 6 additions & 18 deletions SPAM/ESR_SoilEvap.for
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,6 @@
REAL A, B, RedFac, SW_threshold
REAL, DIMENSION(NL) :: DLAYR, DS, DUL, LL, MEANDEP
REAL, DIMENSION(NL) :: SWAD, SWTEMP, SW_AVAIL, ES_Coef
LOGICAL PMcover
REAL PMFRACTION

!-----------------------------------------------------------------------
Expand All @@ -75,8 +74,7 @@
DUL = SOILPROP % DUL
LL = SOILPROP % LL
NLAYR = SOILPROP % NLAYR
PMcover = SOILPROP % PMcover
PMFRACTION = SOILPROP % PMFRACTION
CALL GET("PM", "PMFRACTION", PMFRACTION)

ES = 0.0

Expand Down Expand Up @@ -145,6 +143,11 @@
!-----------------------------------------------------------------------

SWDELTU(L) = -(SWTEMP(L) - SWAD(L)) * ES_Coef(L) !mm3/mm3

! Apply the fraction of plastic mulch coverage
IF (PMFRACTION .GT. 0.0) THEN
SWDELTU(L) = SWDELTU(L) * (1.0 - PMFRACTION)
END IF

! Limit to available water
SW_AVAIL(L) = SW(L) + SWDELTS(L) - SWAD(L)
Expand All @@ -154,9 +157,6 @@

! Limit to negative values (decrease SW)
SWDELTU(L) = AMIN1(0.0, SWDELTU(L))

! Apply the fraction of plastic mulch coverage
SWDELTU(L) = SWDELTU(L) * (1 - PMFRACTION)

! Aggregate soil evaporation from each layer
ES_LYR(L) = -SWDELTU(L) * DLAYR(L) * 10. !mm
Expand All @@ -177,18 +177,6 @@
DO L = NLAYR-1, 1, -1
UPFLOW(L) = UPFLOW(L+1) + ES_LYR(L) / 10. !cm/d
ENDDO

IF (PMCover) THEN
ES = ES * (1 - PMFRACTION)
ES_LYR = ES_LYR * (1 - PMFRACTION)
SWDELTU = SWDELTU * (1 - PMFRACTION)
UPFLOW = UPFLOW * (1 - PMFRACTION)
! DO L = 1, NLAYR
! ES_LYR(L) = ES_LYR(L) * (1 - PMFRACTION)
! SWDELTU(L) = SWDELTU(L) * (1 - PMFRACTION)
! UPFLOW(L) = UPFLOW(L) * (1 - PMFRACTION)
! ENDDO
ENDIF

!-----------------------------------------------------------------------
RETURN
Expand Down
20 changes: 8 additions & 12 deletions SPAM/SOILEV.for
Original file line number Diff line number Diff line change
Expand Up @@ -28,14 +28,14 @@ C 03/30/2000 CHP Keep original value of WINF for export to soil N module
! Calls: ESUP
C=======================================================================
SUBROUTINE SOILEV(DYNAMIC,
& DLAYR, DUL, EOS, LL, SW, !Input
& SW_AVAIL,U, WINF, SOILPROP, !Input
& DLAYR, DUL, EOS, LL, SW, SW_AVAIL, U, WINF, !Input
& ES) !Output

!-----------------------------------------------------------------------
USE ModuleDefs !Definitions of constructed variable types,
! which contain control information, soil
! parameters, hourly weather data.
USE ModuleData
IMPLICIT NONE
SAVE

Expand All @@ -49,8 +49,6 @@ C=======================================================================
REAL ES, T
REAL AWEV1, ESX, SWR, USOIL
REAL DLAYR(NL), DUL(NL), LL(NL), SW(NL)
TYPE (SoilType), INTENT(IN) :: SOILPROP !Soil properties
LOGICAL PMcover
REAL PMFRACTION

!***********************************************************************
Expand Down Expand Up @@ -79,8 +77,7 @@ C-----------------------------------------------------------------------
T= (SUMES2/3.5)**2
ENDIF

PMcover = SOILPROP % PMcover
PMFRACTION = SOILPROP % PMFRACTION
CALL GET("PM", "PMFRACTION", PMFRACTION)

!-----------------------------------------------------------------------
! Set air dry water content for top soil layer
Expand Down Expand Up @@ -160,6 +157,11 @@ C-----------------------------------------------------------------------
ENDIF
ENDIF

! Apply the fraction of plastic mulch coverage
IF (PMFRACTION .GT. 0.0) THEN
ES = ES * (1.0 - PMFRACTION)
ENDIF

!-----------------------------------------------------------------------
! Available water = SW - air dry limit + infil. or sat. flow
SWMIN = MAX(0.0, SW_AVAIL - SWEF * LL(1))
Expand All @@ -170,12 +172,6 @@ C-----------------------------------------------------------------------
ENDIF
ES = MAX(ES, 0.0)


! Apply the fraction of plastic mulch coverage
IF (PMCover) THEN
ES = ES * (1 - PMFRACTION)
ENDIF

!***********************************************************************
!***********************************************************************
! END OF DYNAMIC IF CONSTRUCT
Expand Down
4 changes: 2 additions & 2 deletions SPAM/SPAM.for
Original file line number Diff line number Diff line change
Expand Up @@ -190,7 +190,7 @@ C=======================================================================
CASE ('R') !Original soil evaporation routine
CALL SOILEV(SEASINIT,
& DLAYR, DUL, EOS, LL, SW, SW_AVAIL(1), !Input
& U, WINF,SOILPROP, !Input
& U, WINF, !Input
& ES) !Output
! ----------------------------
! CASE ('S') !SALUS soil evaporation routine
Expand Down Expand Up @@ -359,7 +359,7 @@ C and total potential water uptake rate.
ENDDO
CALL SOILEV(RATE,
& DLAYR, DUL, EOS_SOIL, LL, SW, !Input
& SW_AVAIL(1), U, WINF, SOILPROP, !Input
& SW_AVAIL(1), U, WINF, !Input
& ES) !Output

! ------------------------
Expand Down
7 changes: 3 additions & 4 deletions Soil/SoilUtilities/SOILDYN.for
Original file line number Diff line number Diff line change
Expand Up @@ -2254,18 +2254,17 @@ C=======================================================================
ENDIF
ENDIF
SOILPROP % PMCover = PMCover
SOILPROP % PMFRACTION = 0
PMFRACTION = 0.0
IF (PMCover) THEN
if (PMWD .GE. ROWSPC_CM) THEN
SOILPROP % SALB = PMALB
ENDIF
PMFRACTION = PMWD / ROWSPC_CM
MSALB = PMALB * PMFRACTION + SOILPROP % SALB * (1. - PMFRACTION)
SOILPROP % PMFRACTION = PMFRACTION
MSALB = PMALB * PMFRACTION + SOILPROP % SALB * (1.0 - PMFRACTION)
SOILPROP % MSALB = MSALB
SOILPROP % CMSALB = MSALB
ENDIF
CALL PUT("PM", "PMFRACTION", PMFRACTION)
RETURN
END SUBROUTINE SETPM
14 changes: 9 additions & 5 deletions Soil/SoilWater/RNOFF.for
Original file line number Diff line number Diff line change
Expand Up @@ -19,15 +19,15 @@ C 09/01/1999 GH Incorporated into CROPGRO
! Calls: None
C=======================================================================
SUBROUTINE RNOFF(
& CN, LL, MEINF, MULCH, SAT, SW, WATAVL,SOILPROP, !Input
& CN, LL, MEINF, MULCH, SAT, SW, WATAVL, !Input
& RUNOFF) !Output

C-----------------------------------------------------------------------
USE ModuleDefs
USE ModuleDefs
USE ModuleData
IMPLICIT NONE
SAVE

TYPE (SoilType), INTENT(IN) :: SOILPROP !Soil properties
CHARACTER*1 MEINF
CHARACTER*6 ERRKEY
PARAMETER (ERRKEY = 'RNOFF')
Expand All @@ -44,6 +44,9 @@ C-----------------------------------------------------------------------

! Mulch layer
Type (MulchType) MULCH

! Plastic Mulch
REAL PMFRACTION

!! Temporary for printing
! INTEGER DOY, YEAR, LUN
Expand Down Expand Up @@ -106,8 +109,9 @@ C-----------------------------------------------------------------------
RUNOFF = 0.0
ENDIF

IF (SOILPROP % PMcover) THEN
RUNOFF = WATAVL * SOILPROP % PMFRACTION + RUNOFF * (1 - SOILPROP % PMFRACTION)
CALL GET("PM", "PMFRACTION", PMFRACTION)
IF (PMFRACTION .GT. 0.0) THEN
RUNOFF = WATAVL * PMFRACTION + RUNOFF * (1.0 - PMFRACTION)
ENDIF

!! Temporary
Expand Down
4 changes: 2 additions & 2 deletions Soil/SoilWater/WATBAL.for
Original file line number Diff line number Diff line change
Expand Up @@ -322,8 +322,8 @@ C Conflict with CERES-Wheat
ENDIF

CALL RNOFF(
& CN, LL, MEINF, MULCH, SAT, SW, WATAVL, SOILPROP, !Input
& RUNOFF) !Output
& CN, LL, MEINF, MULCH, SAT, SW, WATAVL, !Input
& RUNOFF) !Output

WINF = WATAVL - RUNOFF + IRRAMT !(mm)
ENDIF
Expand Down
21 changes: 17 additions & 4 deletions Utilities/ModuleDefs.for
Original file line number Diff line number Diff line change
Expand Up @@ -206,10 +206,6 @@ C CHP Added TRTNUM to CONTROL variable.
! REAL, DIMENSION(NL) :: EXTAL, EXTFE, EXTMN,
! REAL, DIMENSION(NL) :: EXMG, EXTS, SLEC

! Flag for plastic mulch
LOGICAL PMCover
REAL PMFRACTION

END TYPE SoilType

!=======================================================================
Expand Down Expand Up @@ -484,6 +480,10 @@ C CHP Added TRTNUM to CONTROL variable.
REAL BETALS
END TYPE

TYPE PMDataType
REAL PMFRACTION
END TYPE

! Data which can be transferred between modules
Type TransferType
Type (ControlType) CONTROL
Expand All @@ -498,6 +498,7 @@ C CHP Added TRTNUM to CONTROL variable.
Type (WatType) WATER
Type (WeathType) WEATHER
TYPE (PDLABETATYPE) PDLABETA
TYPE (PMDataType) PM
End Type TransferType

! The variable SAVE_data contains all of the components to be
Expand Down Expand Up @@ -737,6 +738,12 @@ C CHP Added TRTNUM to CONTROL variable.
CASE('BETA'); Value = SAVE_data % PDLABETA % BETALS
CASE DEFAULT; ERR = .TRUE.
END SELECT

CASE ('PM')
SELECT CASE(VarName)
CASE('PMFRACTION'); Value = SAVE_data % PM % PMFRACTION
CASE DEFAULT; ERR = .TRUE.
END SELECT

Case DEFAULT; ERR = .TRUE.
END SELECT
Expand Down Expand Up @@ -852,6 +859,12 @@ C CHP Added TRTNUM to CONTROL variable.
CASE('BETA'); SAVE_data % PDLABETA % BETALS = Value
CASE DEFAULT; ERR = .TRUE.
END SELECT

CASE ('PM')
SELECT CASE(VarName)
CASE('PMFRACTION'); SAVE_data % PM % PMFRACTION = Value
CASE DEFAULT; ERR = .TRUE.
END SELECT

Case DEFAULT; ERR = .TRUE.
END SELECT
Expand Down

0 comments on commit 44053ea

Please sign in to comment.