Skip to content

Commit

Permalink
Add impedance factor to hydraulic conductivity in VSF.
Browse files Browse the repository at this point in the history
  • Loading branch information
zhangsp8 committed Dec 21, 2024
1 parent 5a5566a commit 50702f2
Show file tree
Hide file tree
Showing 3 changed files with 17 additions and 4 deletions.
4 changes: 2 additions & 2 deletions main/HYDRO/MOD_Catch_LateralFlow.F90
Original file line number Diff line number Diff line change
Expand Up @@ -272,7 +272,7 @@ SUBROUTINE lateral_flow (deltime)
CALL mpi_allreduce (MPI_IN_PLACE, toldis, 1, MPI_REAL8, MPI_SUM, p_comm_worker, p_err)
#endif
IF (p_iam_worker == 0) THEN
write(*,'(A,F10.5,A,ES10.3,A,ES10.3,A)') 'Total surface water error: ', dtolw, &
write(*,'(A,F10.2,A,ES10.3,A,ES10.3,A)') 'Total surface water error: ', dtolw, &
'(m^3) in area ', landarea, '(m^2), discharge ', toldis, '(m^3)'
ENDIF

Expand All @@ -282,7 +282,7 @@ SUBROUTINE lateral_flow (deltime)
CALL mpi_allreduce (MPI_IN_PLACE, dtolw, 1, MPI_REAL8, MPI_SUM, p_comm_worker, p_err)
#endif
IF (p_iam_worker == 0) THEN
write(*,'(A,F10.5,A,ES10.3,A)') 'Total ground water error: ', dtolw, &
write(*,'(A,F10.2,A,ES10.3,A)') 'Total ground water error: ', dtolw, &
'(m^3) in area ', landarea, '(m^2)'
ENDIF
ENDIF
Expand Down
14 changes: 13 additions & 1 deletion main/MOD_SoilSnowHydrology.F90
Original file line number Diff line number Diff line change
Expand Up @@ -683,6 +683,7 @@ SUBROUTINE WATER_VSF (ipatch, patchtype,is_dry_lake, lb, nl_soil, deltim ,&
type(cell_data_struct) :: cell
real(r8) :: wliq_soisno_tmp(1:nl_soil)

real(r8), parameter :: e_ice=6.0 !soil ice impedance factor

!=======================================================================
! [1] update the liquid water within snow layer and the water onto soil
Expand Down Expand Up @@ -1020,6 +1021,16 @@ SUBROUTINE WATER_VSF (ipatch, patchtype,is_dry_lake, lb, nl_soil, deltim ,&
ENDIF
#endif

DO j = 1, nl_soil
IF(t_soisno(j) <= tfrz) THEN
! consider impedance factor
vol_ice(j) = max(min(porsl(j), wice_soisno(j)/(dz_soisno(j)*denice)), 0.)
icefrac(j) = vol_ice(j)/porsl(j)
imped = 10.**(-e_ice*icefrac(j))
hk(j) = imped * hk(j)
ENDIF
ENDDO

#ifndef CatchLateralFlow
err_solver = (sum(wliq_soisno(1:))+sum(wice_soisno(1:))+wa+wdsrf) - w_sum &
- (gwat-etr-rsur-rsubst)*deltim
Expand All @@ -1044,7 +1055,8 @@ SUBROUTINE WATER_VSF (ipatch, patchtype,is_dry_lake, lb, nl_soil, deltim ,&

#if(defined CoLMDEBUG)
IF(abs(err_solver) > 1.e-3)THEN
write(6,'(A,E20.5,I0)') 'Warning (WATER_VSF): water balance violation', err_solver,landpatch%eindex(ipatch)
write(6,'(A,E20.5,A,I0)') 'Warning (WATER_VSF): water balance violation', err_solver, &
' in element ', landpatch%eindex(ipatch)
ENDIF
IF (any(wliq_soisno < -1.e-3)) THEN
write(6,'(A,10E20.5)') 'Warning (WATER_VSF): negative soil water', wliq_soisno(1:nl_soil)
Expand Down
3 changes: 2 additions & 1 deletion share/MOD_SPMD_Task.F90
Original file line number Diff line number Diff line change
Expand Up @@ -331,11 +331,12 @@ SUBROUTINE CoLM_stop (mesg)

IMPLICIT NONE
character(len=*), optional :: mesg
integer :: errorcode

IF (present(mesg)) write(*,*) trim(mesg)

#ifdef USEMPI
CALL mpi_abort (p_comm_glb, p_err)
CALL mpi_abort (p_comm_glb, errorcode, p_err)
#else
STOP
#endif
Expand Down

0 comments on commit 50702f2

Please sign in to comment.