SUBROUTINE update_hmonth_update_vars() USE pd_dates_vars USE pd_update_vars USE pd_report_vars USE pd_var_tables IMPLICIT NONE include "w1clig.inc" ! precip include "p1werm.inc" ! mntime (maximum # of time steps/day) include "w1wind.inc" ! awu(mntime), awudmx include "w1pavg.inc" ! awdair include "m1sim.inc" ! ntstep (actual # of time steps/day) include "h1et.inc" ! ah0drat (dryness ratio) include "h1db1.inc" ! ahzsnd(s) snow depth in mm INTEGER :: i ! local loop variables INTEGER :: s ! local variable (subregion) REAL :: we !variables summed for period hmonth_update(Precipi)%val = hmonth_update(Precipi)%val + awzdpt hmonth_update(Precipi)%cnt = hmonth_update(Precipi)%cnt + 1 !variables running averaged for period we = 0.0 IF (awudmx > 8.0) THEN DO i = 1, ntstep IF (awu(i) > 8.0) THEN we = we + 0.5*awdair*(awu(i)**2) * (awu(i) - 8.0) * & (86400.0/ntstep) * (0.001) ! (s/day) and (J/kJ) END IF END DO END IF CALL run_ave(hmonth_update(Wind_energy), we, 1) CALL run_ave(hmonth_update(Dryness_ratio), ah0drat, 1) s = 1 !currently have only one subregion ! Note that the 20mm depth should be a global parameter ! It is currently stuck in erosion.for as a local parameter there IF (ahzsnd(s) > 20.0) THEN CALL run_ave(hmonth_update(Snow_cover), 1.0, 1) ELSE CALL run_ave(hmonth_update(Snow_cover), 0.0, 1) END IF END SUBROUTINE update_hmonth_update_vars SUBROUTINE update_hmonth_report_vars(cur_day, cur_month, cur_yr, nrot_yrs) USE pd_dates_vars USE pd_update_vars USE pd_report_vars USE pd_var_tables IMPLICIT NONE INTEGER, INTENT (IN) :: cur_day INTEGER, INTENT (IN) :: cur_month INTEGER, INTENT (IN) :: cur_yr INTEGER, INTENT (IN) :: nrot_yrs INTEGER :: cur_rotyr INTEGER :: i, p ! local loop variables cur_rotyr = mod(cur_yr-1,nrot_yrs)+1 ! compute the hmonth period for: ! "first period in current month of current rotation year" p = 24 * (cur_rotyr - 1) + (cur_month - 1) * 2 + 1 ! check if "second period in current month of current rotation year" IF (cur_day > 14) THEN p = p + 1 END IF !variables averaged for reporting period CALL run_ave (hmonth_report(Precipi,p), & hmonth_update(Precipi)%val, 1 ) CALL run_ave (hmonth_report(Wind_energy,p), & hmonth_update(Wind_energy)%val, 1 ) CALL run_ave (hmonth_report(Dryness_ratio,p), & hmonth_update(Dryness_ratio)%val, 1 ) CALL run_ave (hmonth_report(Snow_cover,p), & hmonth_update(Snow_cover)%val, 1 ) ! reset update_vars DO i=1,Max_hmonth_vars hmonth_update(i)%cnt = 0 hmonth_update(i)%val = 0.0 IF (p == (nrot_yrs*24)) THEN hmonth_update(i)%date => hmonth_dates(1) ELSE hmonth_update(i)%date => hmonth_dates(p+1) END IF END DO END SUBROUTINE update_hmonth_report_vars