Skip to content

Commit

Permalink
Merge pull request #94 from GreyEvenson-NOAA/noah_om_grid_snowt_avg_fix
Browse files Browse the repository at this point in the history
Patch SNOWT_AVG and ACSNOM
  • Loading branch information
GreyREvenson authored Dec 18, 2023
2 parents 1739dac + a75492c commit 50069ad
Show file tree
Hide file tree
Showing 3 changed files with 9 additions and 2 deletions.
5 changes: 4 additions & 1 deletion src/EnergyType.f90
Original file line number Diff line number Diff line change
Expand Up @@ -336,7 +336,8 @@ subroutine InitDefault(this)

this%LH = huge(1.0)
this%TGS = huge(1.0)
this%ICE = huge(1)
this%ICE = huge(1)
this%SNOWT_AVG = huge(1.0)

this%IMELT(:) = huge(1)
this%STC(:) = huge(1.0)
Expand Down Expand Up @@ -384,6 +385,7 @@ subroutine TransferIn(this, energygrid, ix, iy)
integer, intent(in) :: ix
integer, intent(in) :: iy

this%SNOWT_AVG = energygrid%SNOWT_AVG(ix,iy)
this%TV = energygrid%TV(ix,iy)
this%TG = energygrid%TG(ix,iy)
this%FCEV = energygrid%FCEV(ix,iy)
Expand Down Expand Up @@ -525,6 +527,7 @@ subroutine TransferOut(this, energygrid, ix, iy)
integer, intent(in) :: ix
integer, intent(in) :: iy

energygrid%SNOWT_AVG(ix,iy) = this%SNOWT_AVG
energygrid%TV(ix,iy) = this%TV
energygrid%TG(ix,iy) = this%TG
energygrid%FCEV(ix,iy) = this%FCEV
Expand Down
3 changes: 2 additions & 1 deletion src/SnowWaterModule.f90
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,7 @@ SUBROUTINE SnowWater (domain, levels, parameters, energy, water, forcing)
! ------------------------ local variables ---------------------------
INTEGER :: IZ,i
REAL :: BDSNOW !bulk density of snow (kg/m3)
REAL :: realMissing = -999999.0
! ----------------------------------------------------------------------

! initialization
Expand Down Expand Up @@ -98,7 +99,7 @@ SUBROUTINE SnowWater (domain, levels, parameters, energy, water, forcing)
energy%SNOWT_AVG = SUM(energy%STC(-levels%nsnow+1:0)*(water%SNICE(-levels%nsnow+1:0)+water%SNLIQ(-levels%nsnow+1:0))) / &
SUM(water%SNICE(-levels%nsnow+1:0)+water%SNLIQ(-levels%nsnow+1:0))
else
energy%SNOWT_AVG = huge(1.)
energy%SNOWT_AVG = realMissing
end if

END SUBROUTINE SnowWater
Expand Down
3 changes: 3 additions & 0 deletions src/WaterType.f90
Original file line number Diff line number Diff line change
Expand Up @@ -137,6 +137,7 @@ subroutine InitDefault(this)

class(water_type), intent(inout) :: this

this%ACSNOM = huge(1.0)
this%qinsur = huge(1.0)
this%qseva = huge(1.0)
this%EVAPOTRANS = huge(1.0)
Expand Down Expand Up @@ -226,6 +227,7 @@ subroutine TransferIn(this, watergrid, ix, iy)
integer, intent(in) :: ix
integer, intent(in) :: iy

this%ACSNOM = watergrid%ACSNOM(ix,iy)
this%qinsur = watergrid%qinsur(ix,iy)
this%qseva = watergrid%qseva(ix,iy)
this%EVAPOTRANS = watergrid%EVAPOTRANS(ix,iy)
Expand Down Expand Up @@ -306,6 +308,7 @@ subroutine TransferOut(this, watergrid, ix, iy)
integer, intent(in) :: ix
integer, intent(in) :: iy

watergrid%ACSNOM(ix,iy) = this%ACSNOM
watergrid%qinsur(ix,iy) = this%qinsur
watergrid%qseva(ix,iy) = this%qseva
watergrid%EVAPOTRANS(ix,iy) = this%EVAPOTRANS
Expand Down

0 comments on commit 50069ad

Please sign in to comment.