Skip to content

Commit

Permalink
fixed div. changes from local LIS config
Browse files Browse the repository at this point in the history
  • Loading branch information
Justin A. Pflug committed Jun 6, 2023
1 parent 224fe18 commit 7d35aad
Show file tree
Hide file tree
Showing 4 changed files with 14 additions and 31 deletions.
4 changes: 2 additions & 2 deletions lis/surfacemodels/land/noahmp.4.0.1/noahmp_driver_401.F90
100755 → 100644
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,7 @@ subroutine noahmp_driver_401(n, ttile, itimestep, &
integer, intent(in) :: snf_opt ! precipitation partitioning between snow and rain
! (1-Jordan91; 2->BATS: Snow when SFCTMP < TFRZ+2.2;
! 3->Noah: Snow when SFCTMP < TFRZ;
! 4->Use WRF precipitation partitioning;
! 4->Use WRF precipitation partitioning
! 5->Use linear relationship from SnowModel, based on Dai (2008))
integer, intent(in) :: tbot_opt ! lower boundary of soil temperature (1->zero-flux; 2->Noah)
integer, intent(in) :: stc_opt ! snow/soil temperature time scheme (1->semi-implicit; 2->fully implicit)
Expand Down Expand Up @@ -743,7 +743,7 @@ subroutine noahmp_driver_401(n, ttile, itimestep, &
fldfrcin(1,1)=fldfrc


call noahmplsm_401 (ttile,LIS_rc%udef, & ! in : LIS undefined value (David Mocko)
call noahmplsm_401 (LIS_rc%udef, & ! in : LIS undefined value (David Mocko)
itimestep,yearlen , julian , coszin , latin , lonin , & ! in : time/space-related
dz8w3d(1), dt , zsoil , nsoil , dx , & ! in : model configuration
vegetypein, soiltypein, vegfrain, vegmaxin, tbotin , & ! in : Vegetation/Soil characteristics
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -280,11 +280,10 @@ SUBROUTINE NOAHMP_GLACIER (&
FGEV = EDIR * LATHEA
END IF

! MLW remove message
! IF(MAXVAL(SICE) < 0.0001) THEN
! WRITE(message,*) "GLACIER HAS MELTED AT:",ILOC,JLOC," ARE YOU SURE THIS SHOULD BE A GLACIER POINT?"
! CALL wrf_debug(10,TRIM(message))
! END IF
IF(MAXVAL(SICE) < 0.0001) THEN
WRITE(message,*) "GLACIER HAS MELTED AT:",ILOC,JLOC," ARE YOU SURE THIS SHOULD BE A GLACIER POINT?"
CALL wrf_debug(10,TRIM(message))
END IF

! water and energy balance check

Expand Down Expand Up @@ -3044,7 +3043,7 @@ SUBROUTINE ERROR_GLACIER (ILOC ,JLOC ,SWDOWN ,FSA ,FSR ,FIRA , &
call wrf_message(trim(message))
WRITE(message,'(i6,1x,i6,1x,5F10.4)')ILOC,JLOC,SAG,FIRA,FSH,FGEV,SSOIL
call wrf_message(trim(message))
! call wrf_error_fatal("Energy budget problem in NOAHMP GLACIER")
call wrf_error_fatal("Energy budget problem in NOAHMP GLACIER")
END IF

END_WB = SNEQV
Expand Down
15 changes: 7 additions & 8 deletions lis/surfacemodels/land/noahmp.4.0.1/phys/module_sf_noahmpdrv_401.F90
100755 → 100644
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ MODULE module_sf_noahmpdrv_401
!
CONTAINS
! The subroutine name has been modifed for LIS implemenation Oct 22 2018
SUBROUTINE noahmplsm_401(tid,LIS_undef_value, & ! IN : LIS undefined value
SUBROUTINE noahmplsm_401(LIS_undef_value, & ! IN : LIS undefined value
ITIMESTEP, YR, JULIAN, COSZIN,XLAT,XLONG, & ! IN : Time/Space-related
DZ8W, DT, DZS, NSOIL, DX, & ! IN : Model configuration
IVGTYP, ISLTYP, VEGFRA, VEGMAX, TMN, & ! IN : Vegetation/Soil characteristics
Expand Down Expand Up @@ -72,8 +72,7 @@ SUBROUTINE noahmplsm_401(tid,LIS_undef_value,

! IN only

! Added LIS undefined value as an input - David Mocko
integer :: tid
! Added LIS undefined value as an input - David Mocko
REAL, INTENT(IN ) :: LIS_undef_value
INTEGER, INTENT(IN ) :: ITIMESTEP ! timestep number
INTEGER, INTENT(IN ) :: YR ! 4-digit year
Expand Down Expand Up @@ -103,7 +102,7 @@ SUBROUTINE noahmplsm_401(tid,LIS_undef_value,
INTEGER, INTENT(IN ) :: IOPT_INF ! frozen soil permeability (1-> NY06; 2->Koren99)
INTEGER, INTENT(IN ) :: IOPT_RAD ! radiation transfer (1->gap=F(3D,cosz); 2->gap=0; 3->gap=1-Fveg)
INTEGER, INTENT(IN ) :: IOPT_ALB ! snow surface albedo (1->BATS; 2->CLASS)
INTEGER, INTENT(IN ) :: IOPT_SNF ! rainfall & snowfall (1-Jordan91; 2->BATS;3->Noah; 5->SnowModel+Dai(2008))
INTEGER, INTENT(IN ) :: IOPT_SNF ! rainfall & snowfall (1-Jordan91; 2->BATS; 3->Noah)
INTEGER, INTENT(IN ) :: IOPT_TBOT ! lower boundary of soil temperature (1->zero-flux; 2->Noah)
INTEGER, INTENT(IN ) :: IOPT_STC ! snow/soil temperature time scheme
INTEGER, INTENT(IN ) :: IOPT_GLA ! glacier option (1->phase change; 2->simple)
Expand Down Expand Up @@ -879,7 +878,7 @@ SUBROUTINE noahmplsm_401(tid,LIS_undef_value,

ICE=0 ! Neither sea ice or land ice.
CALL NOAHMP_SFLX (parameters, &
tid , J , LAT , YEARLEN , JULIAN , COSZ , & ! IN : Time/Space-related
I , J , LAT , YEARLEN , JULIAN , COSZ , & ! IN : Time/Space-related
DT , DX , DZ8W1D , NSOIL , ZSOIL , NSNOW , & ! IN : Model configuration
FVEG , FVGMAX , VEGTYP , ICE , IST , CROPTYPE, & ! IN : Vegetation/Soil characteristics
SMCEQ , & ! IN : Vegetation/Soil characteristics
Expand Down Expand Up @@ -1603,9 +1602,9 @@ SUBROUTINE NOAHMP_INIT ( MMINLU, SNOW , SNOWH , CANWAT , ISLTYP , IVGTYP, XLAT
,i,j,snow(i,j),snowh(i,j)
CALL wrf_message(err_message)
ENDIF
IF ( SNOW( i,j ) > 10000. ) THEN
SNOWH(I,J) = SNOWH(I,J) * 10000. / SNOW(I,J) ! SNOW in mm and SNOWH in m
SNOW (I,J) = 10000. ! cap SNOW at 2000, maintain density
IF ( SNOW( i,j ) > 2000. ) THEN
SNOWH(I,J) = SNOWH(I,J) * 2000. / SNOW(I,J) ! SNOW in mm and SNOWH in m
SNOW (I,J) = 2000. ! cap SNOW at 2000, maintain density
ENDIF
ENDDO
ENDDO
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6995,31 +6995,22 @@ SUBROUTINE COMBINE (parameters,NSNOW ,NSOIL ,ILOC ,JLOC , & !in
ISNOW_OLD = ISNOW

DO J = ISNOW_OLD+1,0
! print *,'H1'
IF (SNICE(J) <= .1) THEN
! print *,'H2'
IF(J /= 0) THEN
! print *,'H3'
SNLIQ(J+1) = SNLIQ(J+1) + SNLIQ(J)
SNICE(J+1) = SNICE(J+1) + SNICE(J)
ELSE
! print *,'H4'
IF (ISNOW_OLD < -1) THEN ! MB/KM: change to ISNOW
! print *,'H5'
SNLIQ(J-1) = SNLIQ(J-1) + SNLIQ(J)
SNICE(J-1) = SNICE(J-1) + SNICE(J)
ELSE
! print *,'H6'
IF(SNICE(J) >= 0.) THEN
! print *,'H7'
PONDING1 = SNLIQ(J) ! ISNOW WILL GET SET TO ZERO BELOW; PONDING1 WILL GET
SNEQV = SNICE(J) ! ADDED TO PONDING FROM PHASECHANGE PONDING SHOULD BE
SNOWH = DZSNSO(J) ! ZERO HERE BECAUSE IT WAS CALCULATED FOR THIN SNOW
ELSE ! SNICE OVER-SUBLIMATED EARLIER
! print *,'H8'
PONDING1 = SNLIQ(J) + SNICE(J)
IF(PONDING1 < 0.) THEN ! IF SNICE AND SNLIQ SUBLIMATES REMOVE FROM SOIL
! print *,'H9'
SICE(1) = MAX(0.0,SICE(1)+PONDING1/(DZSNSO(1)*1000.))
PONDING1 = 0.0
END IF
Expand All @@ -7036,7 +7027,6 @@ SUBROUTINE COMBINE (parameters,NSNOW ,NSOIL ,ILOC ,JLOC , & !in

! shift all elements above this down by one.
IF (J > ISNOW+1 .AND. ISNOW < -1) THEN
! print *,'H10'
DO I = J, ISNOW+2, -1
STC(I) = STC(I-1)
SNLIQ(I) = SNLIQ(I-1)
Expand All @@ -7051,7 +7041,6 @@ SUBROUTINE COMBINE (parameters,NSNOW ,NSOIL ,ILOC ,JLOC , & !in
! to conserve water in case of too large surface sublimation

IF(SICE(1) < 0.) THEN
! print *,'H11'
SH2O(1) = SH2O(1) + SICE(1)
SICE(1) = 0.
END IF
Expand All @@ -7064,7 +7053,6 @@ SUBROUTINE COMBINE (parameters,NSNOW ,NSOIL ,ILOC ,JLOC , & !in
ZWLIQ = 0.

DO J = ISNOW+1,0
! print *,'H12'
SNEQV = SNEQV + SNICE(J) + SNLIQ(J)
SNOWH = SNOWH + DZSNSO(J)
ZWICE = ZWICE + SNICE(J)
Expand All @@ -7076,7 +7064,6 @@ SUBROUTINE COMBINE (parameters,NSNOW ,NSOIL ,ILOC ,JLOC , & !in

IF (SNOWH < 0.025 .AND. ISNOW < 0 ) THEN ! MB: change limit
! IF (SNOWH < 0.05 .AND. ISNOW < 0 ) THEN
! print *,'H13'
ISNOW = 0
SNEQV = ZWICE
PONDING2 = ZWLIQ ! LIMIT OF ISNOW < 0 MEANS INPUT PONDING
Expand All @@ -7093,14 +7080,12 @@ SUBROUTINE COMBINE (parameters,NSNOW ,NSOIL ,ILOC ,JLOC , & !in
! check the snow depth - snow layers combined

IF (ISNOW < -1) THEN
! print *,'H14'

ISNOW_OLD = ISNOW
MSSI = 1

DO I = ISNOW_OLD+1,0
IF (DZSNSO(I) < DZMIN(MSSI)) THEN
! print *,'H15'

IF (I == ISNOW+1) THEN
NEIBOR = I + 1
Expand Down

0 comments on commit 7d35aad

Please sign in to comment.