Skip to content
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
9 changes: 7 additions & 2 deletions drivers/wrf/module_sf_noahmpdrv.F
Original file line number Diff line number Diff line change
Expand Up @@ -2004,7 +2004,7 @@ SUBROUTINE NOAHMP_INIT ( MMINLU, SNOW , SNOWH , CANWAT , ISLTYP , IVGTYP, XLAT
call read_mp_crop_parameters()
call read_tiledrain_parameters()
call read_mp_optional_parameters()
if(iopt_irr >= 1) call read_mp_irrigation_parameters()
call read_mp_irrigation_parameters(iopt_irr)

IF( .NOT. restart ) THEN

Expand Down Expand Up @@ -2181,7 +2181,12 @@ SUBROUTINE NOAHMP_INIT ( MMINLU, SNOW , SNOWH , CANWAT , ISLTYP , IVGTYP, XLAT

lai (I,J) = max(lai(i,j),0.05) ! at least start with 0.05 for arbitrary initialization (v3.7)
xsaixy (I,J) = max(0.1*lai(I,J),0.05) ! MB: arbitrarily initialize SAI using input LAI (v3.7)
masslai = 1000. / max(SLA_TABLE(IVGTYP(I,J)),1.0) ! conversion from lai to mass (v3.7)
!Commit 554b12c
if (urbanpt_flag) then
masslai = 1000. / max(SLA_TABLE(NATURAL_TABLE),1.0) ! conversion from lai to mass (v3.7)
else
masslai = 1000. / max(SLA_TABLE(IVGTYP(I,J)),1.0) ! conversion from lai to mass (v3.7)
end if
lfmassxy (I,J) = lai(i,j)*masslai ! use LAI to initialize (v3.7)
masssai = 1000. / 3.0 ! conversion from lai to mass (v3.7)
stmassxy (I,J) = xsaixy(i,j)*masssai ! use SAI to initialize (v3.7)
Expand Down
21 changes: 13 additions & 8 deletions src/module_sf_noahmplsm.F
Original file line number Diff line number Diff line change
Expand Up @@ -4808,9 +4808,9 @@ SUBROUTINE SFCDIF2(parameters,ITER ,Z0 ,THZ0 ,THLM ,SFCSPD , & !in
! ----------------------------------------------------------------------
! LECH'S SURFACE FUNCTIONS
PSLMU (ZZ)= -0.96* log (1.0-4.5* ZZ)
PSLMS (ZZ)= ZZ * RRIC -2.076* (1.0 -1.0/ (ZZ +1.0))
PSLMS (ZZ)= (ZZ / RFC) -2.076* (1.0 -1.0/ (ZZ +1.0))
PSLHU (ZZ)= -0.96* log (1.0-4.5* ZZ)
PSLHS (ZZ)= ZZ * RFAC -2.076* (1.0 -1.0/ (ZZ +1.0))
PSLHS (ZZ)= ZZ * RFAC -2.076* (1.0 - exp(-1.2 * ZZ))
! PAULSON'S SURFACE FUNCTIONS
PSPMU (XX)= -2.0* log ( (XX +1.0)*0.5) - log ( (XX * XX +1.0)*0.5) &
& +2.0* ATAN (XX) &
Expand Down Expand Up @@ -12188,11 +12188,11 @@ subroutine read_mp_crop_parameters()

end subroutine read_mp_crop_parameters

subroutine read_mp_irrigation_parameters()
subroutine read_mp_irrigation_parameters(iopt_irr)
implicit none
integer :: ierr
logical :: file_named

INTEGER, INTENT(in) :: iopt_irr
REAL :: IRR_FRAC ! irrigation Fraction
INTEGER :: IRR_HAR ! number of days before harvest date to stop irrigation
REAL :: IRR_LAI ! Minimum lai to trigger irrigation
Expand All @@ -12216,11 +12216,16 @@ subroutine read_mp_irrigation_parameters()
FIRTFAC_TABLE = -1.0E36 ! flood application rate factor
IR_RAIN_TABLE = -1.0E36 ! maximum precipitation to stop irrigation trigger

inquire( file='MPTABLE.TBL', exist=file_named )
if ( file_named ) then
open(15, file="MPTABLE.TBL", status='old', form='formatted', action='read', iostat=ierr)
if (iopt_irr >= 1) THEN
inquire( file='MPTABLE.TBL', exist=file_named )
if ( file_named ) then
open(15, file="MPTABLE.TBL", status='old', form='formatted', action='read', iostat=ierr)
else
open(15, status='old', form='formatted', action='read', iostat=ierr)
end if
else
open(15, status='old', form='formatted', action='read', iostat=ierr)
! Nothing to read, nothing to do
RETURN
end if

if (ierr /= 0) then
Expand Down