Skip to content

Commit

Permalink
update for runoff parameterization for bidirectional coupling
Browse files Browse the repository at this point in the history
  • Loading branch information
zhongwangwei committed Jul 19, 2024
1 parent b553aa2 commit 0fec9dd
Show file tree
Hide file tree
Showing 3 changed files with 57 additions and 17 deletions.
16 changes: 10 additions & 6 deletions CaMa/src/MOD_CaMa_colmCaMa.F90
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ MODULE MOD_CaMa_colmCaMa
integer(KIND=JPIM) :: ISTEPX ! total time step
integer(KIND=JPIM) :: ISTEPADV ! time step to be advanced within DRV_ADVANCE
real(KIND=JPRB),ALLOCATABLE :: ZBUFF(:,:,:) ! Buffer to store forcing runoff
real(KIND=JPRB),ALLOCATABLE :: ZBUFF_2(:,:,:) ! Buffer to store forcing runoff

INTERFACE colm_CaMa_init
MODULE PROCEDURE colm_CaMa_init
Expand Down Expand Up @@ -206,14 +207,16 @@ SUBROUTINE colm_CaMa_init
allocate (fevpg_2d (NX,NY))
allocate (finfg_2d (NX,NY))
!allocate data buffer for input forcing, flood fraction and flood depth
allocate (ZBUFF(NX,NY,4))
allocate (ZBUFF(NX,NY,2))
allocate (ZBUFF_2(NX,NY,2))
allocate (fldfrc_tmp(NX,NY))
allocate (flddepth_tmp(NX,NY))
!Initialize the data buffer for input forcing, flood fraction and flood depth
runoff_2d(:,:) = 0.0D0 !runoff in master processor
fevpg_2d(:,:) = 0.0D0 !evaporation in master processor
finfg_2d(:,:) = 0.0D0 !re-infiltration in master processor
ZBUFF(:,:,:) = 0.0D0 !input forcing in master processor
ZBUFF_2(:,:,:) = 0.0D0 !input forcing in master processor
fldfrc_tmp(:,:) = 0.0D0 !flood fraction in master processor
flddepth_tmp(:,:) = 0.0D0 !flood depth in master processor
ENDIF
Expand Down Expand Up @@ -276,14 +279,14 @@ SUBROUTINE colm_cama_drv(idate_sec)
ZBUFF(i,j,1)=runoff_2d(i,j)/1000.0D0 ! mm/s -->m/s
ZBUFF(i,j,2)=0.0D0
IF (LWEVAP) THEN
ZBUFF(i,j,3)=fevpg_2d(i,j)/1000.0D0 ! mm/s -->m/s
ZBUFF_2(i,j,1)=fevpg_2d(i,j)/1000.0D0 ! mm/s -->m/s
ELSE
ZBUFF(i,j,3)=0.0D0
ZBUFF_2(i,j,1)=0.0D0
ENDIF
IF (LWINFILT) THEN
ZBUFF(i,j,4)=finfg_2d(i,j)/1000.0D0 !mm/s -->m/s
ZBUFF_2(i,j,2)=finfg_2d(i,j)/1000.0D0 !mm/s -->m/s
ELSE
ZBUFF(i,j,4)=0.0D0
ZBUFF_2(i,j,2)=0.0D0
ENDIF
ENDDO
ENDDO
Expand All @@ -294,7 +297,7 @@ SUBROUTINE colm_cama_drv(idate_sec)
! Get the time step of cama-flood simulation
ISTEPADV=INT(DTIN/DT,JPIM)
! Interporlate variables & send to CaMa-Flood
CALL CMF_FORCING_PUT(ZBUFF)
CALL CMF_FORCING_PUT(ZBUFF,ZBUFF_2)
! Advance CaMa-Flood model for ISTEPADV
CALL CMF_DRV_ADVANCE(ISTEPADV)
! Get the flood depth and flood fraction from cama-flood model
Expand Down Expand Up @@ -631,5 +634,6 @@ SUBROUTINE get_fldevp (hu,ht,hq,us,vs,tm,qm,rhoair,psrf,tssea,&
z0m = z0mg
END SUBROUTINE get_fldevp


#endif
END MODULE MOD_CaMa_colmCaMa
8 changes: 5 additions & 3 deletions CaMa/src/cmf_ctrl_forcing_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -628,7 +628,7 @@ END SUBROUTINE CMF_FORCING_COM


!####################################################################
SUBROUTINE CMF_FORCING_PUT(PBUFF)
SUBROUTINE CMF_FORCING_PUT(PBUFF,PBUFF2)
! interporlate with inpmat, then send runoff data to CaMa-Flood
! -- called from "Main Program / Coupler" or CMF_DRV_ADVANCE
! add water re-infiltration calculation
Expand All @@ -637,6 +637,8 @@ SUBROUTINE CMF_FORCING_PUT(PBUFF)
IMPLICIT NONE
! Declaration of arguments
real(KIND=JPRB), intent(in) :: PBUFF(:,:,:)
real(KIND=JPRB), intent(in) :: PBUFF2(:,:,:)

!============================
! Runoff interpolation & unit conversion (mm/dt -> m3/sec)
IF (LINTERP) THEN ! mass conservation using "input matrix table (inpmat)"
Expand All @@ -657,7 +659,7 @@ SUBROUTINE CMF_FORCING_PUT(PBUFF)
ENDIF
IF (LWEVAP) THEN
!IF ( SIZE(PBUFF,3) == 3 ) THEN
CALL ROFF_INTERP(PBUFF(:,:,3),D2WEVAP)
CALL ROFF_INTERP(PBUFF2(:,:,1),D2WEVAP)
!ELSE
! WRITE(LOGNAM,*) "LWEVAP is true but evaporation not provide in input array for interpolation"
! WRITE(LOGNAM,*) "CMF_FORCING_PUT(PBUFF), PBUFF should have 3 fields for interpolation "
Expand All @@ -666,7 +668,7 @@ SUBROUTINE CMF_FORCING_PUT(PBUFF)
ENDIF
IF (LWINFILT) THEN
!IF ( SIZE(PBUFF,3) == 3 ) THEN
CALL ROFF_INTERP(PBUFF(:,:,4),D2WINFILT)
CALL ROFF_INTERP(PBUFF2(:,:,2),D2WINFILT)
!ELSE
! WRITE(LOGNAM,*) "LWINFILT is true but evaporation not provide in input array for interpolation"
! WRITE(LOGNAM,*) "CMF_FORCING_PUT(PBUFF), PBUFF should have 4 fields for interpolation "
Expand Down
50 changes: 42 additions & 8 deletions main/MOD_SoilSnowHydrology.F90
Original file line number Diff line number Diff line change
Expand Up @@ -334,9 +334,26 @@ SUBROUTINE WATER_2014 (ipatch,patchtype,lb ,nl_soil ,deltim,&
! surface runoff from inundation, this should not be added to the surface runoff from soil
! otherwise, the surface runoff will be double counted.
! only the re-infiltration is added to water balance calculation.
CALL SurfaceRunoff_SIMTOP (nl_soil,1.0,wimp,porsl,psi0,hksati,&
z_soisno(1:),dz_soisno(1:),zi_soisno(0:),&
eff_porosity,icefrac,zwt,gfld,rsur_fld)
IF (DEF_Runoff_SCHEME == 0) THEN

CALL SurfaceRunoff_SIMTOP (nl_soil,1.0,wimp,porsl,psi0,hksati,&
z_soisno(1:),dz_soisno(1:),zi_soisno(0:),&
eff_porosity,icefrac,zwt,gfld,rsur_fld)
ELSEIF (DEF_Runoff_SCHEME == 1) THEN
wliq_soisno_tmp(:) = 0
CALL Runoff_VIC(deltim, porsl, theta_r, hksati, bsw, &
wice_soisno(1:nl_soil), wliq_soisno(1:nl_soil), fevpg(ipatch), rootflux, gfld, &
vic_b_infilt(ipatch), vic_Dsmax(ipatch), vic_Ds(ipatch), vic_Ws(ipatch), vic_c(ipatch),&
rsur_fld, rsubst, wliq_soisno_tmp(1:nl_soil))
ELSEIF (DEF_Runoff_SCHEME == 2) THEN
CALL Runoff_XinAnJiang (&
nl_soil, dz_soisno(1:nl_soil), eff_porosity(1:nl_soil), vol_liq(1:nl_soil), &
topostd, gfld, deltim, rsur_fld, rsubst)
ELSEIF (DEF_Runoff_SCHEME == 3) THEN
CALL Runoff_SimpleVIC (&
nl_soil, dz_soisno(1:nl_soil), eff_porosity(1:nl_soil), vol_liq(1:nl_soil), &
BVIC, gfld, deltim, rsur_fld, rsubst)
ENDIF
! infiltration into surface soil layer
qinfl_fld_subgrid = gfld - rsur_fld !assume the re-infiltration is occured in whole patch area.
ELSE
Expand Down Expand Up @@ -818,17 +835,34 @@ SUBROUTINE WATER_VSF (ipatch, patchtype,lb ,nl_soil ,deltim ,&

#if(defined CaMa_Flood)
IF (LWINFILT) THEN
! \ re-infiltration [mm/s] calculation.
! re-infiltration [mm/s] calculation.
! IF surface runoff is ocurred (rsur != 0.), flood depth <1.e-6 and flood frction <0.05,
! the re-infiltration will not be calculated.
IF ((flddepth .gt. 1.e-6).and.(fldfrc .gt. 0.05) .and. (patchtype == 0) ) THEN
gfld=flddepth/deltim ! [mm/s]
! surface runoff from inundation, this should not be added to the surface runoff from soil
! otherwise, the surface runoff will be double counted.
! only the re-infiltration is added to water balance calculation.
CALL SurfaceRunoff_SIMTOP (nl_soil,1.0,wimp,porsl,psi0,hksati,&
z_soisno(1:),dz_soisno(1:),zi_soisno(0:),&
eff_porosity,icefrac,zwt,gfld,rsur_fld)
IF (DEF_Runoff_SCHEME == 0) THEN

CALL SurfaceRunoff_SIMTOP (nl_soil,1.0,wimp,porsl,psi0,hksati,&
z_soisno(1:),dz_soisno(1:),zi_soisno(0:),&
eff_porosity,icefrac,zwt,gfld,rsur_fld)
ELSEIF (DEF_Runoff_SCHEME == 1) THEN
wliq_soisno_tmp(:) = 0
CALL Runoff_VIC(deltim, porsl, theta_r, hksati, bsw, &
wice_soisno(1:nl_soil), wliq_soisno(1:nl_soil), fevpg(ipatch), rootflux, gfld, &
vic_b_infilt(ipatch), vic_Dsmax(ipatch), vic_Ds(ipatch), vic_Ws(ipatch), vic_c(ipatch),&
rsur_fld, rsubst, wliq_soisno_tmp(1:nl_soil))
ELSEIF (DEF_Runoff_SCHEME == 2) THEN
CALL Runoff_XinAnJiang (&
nl_soil, dz_soisno(1:nl_soil), eff_porosity(1:nl_soil), vol_liq(1:nl_soil), &
topostd, gfld, deltim, rsur_fld, rsubst)
ELSEIF (DEF_Runoff_SCHEME == 3) THEN
CALL Runoff_SimpleVIC (&
nl_soil, dz_soisno(1:nl_soil), eff_porosity(1:nl_soil), vol_liq(1:nl_soil), &
BVIC, gfld, deltim, rsur_fld, rsubst)
ENDIF
! infiltration into surface soil layer
qinfl_fld_subgrid = gfld - rsur_fld !assume the re-infiltration is occured in whole patch area.
ELSE
Expand All @@ -838,11 +872,11 @@ SUBROUTINE WATER_VSF (ipatch, patchtype,lb ,nl_soil ,deltim ,&

ENDIF
qinfl_fld=qinfl_fld_subgrid*fldfrc ! [mm/s] re-infiltration in grid.
!qinfl=qinfl_fld+qinfl ! [mm/s] total infiltration in grid.
qgtop=qinfl_fld+qgtop ! [mm/s] total infiltration in grid.
flddepth=flddepth-deltim*qinfl_fld_subgrid ! renew flood depth [mm], the flood depth is reduced by re-infiltration but only in inundation area.
ENDIF
#endif

!=======================================================================
! [3] determine the change of soil water
!=======================================================================
Expand Down

0 comments on commit 0fec9dd

Please sign in to comment.