subbasin_initialise_weather_gen Subroutine

public subroutine subbasin_initialise_weather_gen(amp, avt, ffc, lat, nc, wft, wi)

Uses

  • proc~~subbasin_initialise_weather_gen~~UsesGraph proc~subbasin_initialise_weather_gen subbasin_initialise_weather_gen module~input input proc~subbasin_initialise_weather_gen->module~input module~output output proc~subbasin_initialise_weather_gen->module~output module~utilities utilities module~input->module~utilities module~output->module~utilities

Arguments

Type IntentOptional AttributesName
real(kind=dp), intent(inout), dimension(:):: amp
real(kind=dp), intent(inout), dimension(:):: avt
real(kind=dp), intent(inout), dimension(:):: ffc
real(kind=dp), intent(in), dimension(:):: lat
integer, intent(in), dimension(13):: nc
real(kind=dp), intent(inout), dimension(:, :):: wft
real(kind=dp), intent(inout), dimension(:, :):: wi

Called by

proc~~subbasin_initialise_weather_gen~~CalledByGraph proc~subbasin_initialise_weather_gen subbasin_initialise_weather_gen proc~initialise initialise proc~initialise->proc~subbasin_initialise_weather_gen program~swim swim program~swim->proc~initialise

Contents


Source Code

  subroutine subbasin_initialise_weather_gen(amp, avt, ffc, lat, nc, wft, wi)
    !**** PURPOSE: THIS SUBROUTINE READS MONTHLY STATISTICAL WEATHER PARAMETERS
    !              for the basin from wgen.dat
    !**** CALLED IN: readsub
    !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    !     PARAMETERS & VARIABLES
    !
    !      >>>>> COMMON PARAMETERS & VARIABLES
    !      ATTN: Input parameters read from wgen.dat are BASIN parameters;
    !            Dimension (j) is optional, if subbasin statistics will be availbale
    !      amp(j) = annual amplitude in daily aver. temperature, degree C
    !      avt(j) = average annual air temp, degree C, used in solt()
    !      daylmn(j) = min day length, h
    !      ffc(j) = field capacity, m/m (not used)
    !block nc(m) = number of days passed in the beginning of month
    !      obmn(m, j) = average monthly min temp, degree C
    !      obmx(m, j) = average monthly max temp, degree C
    !      prw(1, m, j) = monthly probability of wet day after dry day
    !      prw(2, m, j) = monthly probability of wet day after wet day
    !      r(8) = vector for output in readwet
    !      rsm(m) = monthly max .5h rain for period of record, mm,
    !                   smoothed wim()
    !      rsmm(m) = monthly number of rainy days
    !      rsmy(m) = monthly rainfall, mm
    !      rst(m, j) = monthly mean event of daily rainfall, mm
    !      tpnyr(j) = number of years of record max .5h rainfall
    !      tp5(j) = 10 year frequency of .5h rainfall (mm)
    !      tp6(j) = 10 year frequency of .6h rainfall (mm)
    !      wft(m, j) = monthly prob. of rainy day
    !      wi(m, j) = f(wim), used in alpha() for estim of precip. alpha factor
    !      wim(m) = monthly max .5h rain for period of record, mm
    !      ylc(j) = cos(lat()/clt), lat() - lat, clt=57.296, for rmx in evap
    !      yls(j) = sin(lat()/clt), lat() - lat, clt=57.296, for rmx in evap
    !                   (convert degrees to radians (2pi/360=1/57.296) )
    !      >>>>> STATIC PARAMETERS
    !      i = subbasin number (IN TITLE)
    !      ch = interm. parameter
    !      f = interm. parameter
    !      h = interm. parameter
    !      ii = cycle parameter
    !      j = cycle parameter
    !      mon = cycle parameter
    !      r25 = interm. parameter
    !      tas = interm. parameter to calc amp()
    !      tav = interm. parameter, monthly mean temp
    !      tbb = interm. parameter to calc amp()
    !      titldum = text
    !      xm = interm. parameter
    !      xx = interm. parameter
    !      xy2 = interm. parameter
    !      ytn = interm. parameter

    use input, only : get_config_fid
    use output, only : output_open_file

    real(dp), dimension(:), intent(inout) :: amp
    real(dp), dimension(:), intent(inout) :: avt
    real(dp), dimension(:), intent(inout) :: ffc
    real(dp), dimension(:), intent(in) :: lat
    integer, dimension(13), intent(in) :: nc
    real(dp), dimension(:, :), intent(inout) :: wft
    real(dp), dimension(:, :), intent(inout) :: wi

    integer i, mon
    real(dp) f, r25, tas, tav, tbb, xm, xx, xy2
    real(dp), dimension(12) :: r, rsm, rsmm, rsmy

    !**** CALCULATION of WEATHER GENERATOR PARAMETERS, step 2
    !     wft() - used in solt, wi() - used in alpha & peakq
    rsm = 0.
    rsmm = 0.
    rsmy = 0.

    rsm(1) = (wim(12) + wim(1) + wim(2)) / 3.
    do mon = 2, 11
      rsm(mon) = (wim(mon - 1) + wim(mon) + wim(mon + 1)) / 3.
    end do
    rsm(12) = (wim(11) + wim(12) + wim(1)) / 3.

    tbb = 0.
    tas = 100.

    do i = 1, mb
      r = 0.
      do mon = 1, 12
        xm = nc(mon + 1) - nc(mon)
        rsmm(mon) = xm * prw(1, mon) / &
                    (1. - prw(2, mon) + prw(1, mon))
        if (rsmm(mon) .le. 0.) rsmm(mon) = .001
        r25 = rst(mon)
        rsmy(mon) = rsmm(mon) * r25
        wft(mon, i) = rsmm(mon) / xm
        xy2 = .5 / tpnyr(i)
        f = xy2 / rsmm(mon)
        wi(mon, i) = - rsm(mon) /log(f)
        wi(mon, i) = 1. - exp(- wi(mon, i) / r25)
        if (wi(mon, i) .lt. .1) wi(mon, i) = .1
        if (wi(mon, i) .gt. .95) wi(mon, i) = .95
        r(1) = r(1) + obmx(mon)
        r(2) = r(2) + obmn(mon)
        r(8) = r(8) + rsmy(mon)

        tav = (obmx(mon) + obmn(mon)) / 2.
        if (tav .gt. tbb) tbb = tav
        if (tav .lt. tas) tas = tav
      end do

      !**** CALCULATION of WEATHER GENERATOR PARAMETERS, step 3
      !     avt(), amp() - used in solt
      xx = lat(i) / clt
      avt(i) = (r(1) + r(2)) / 2. / 12.
      amp(i) = (tbb - tas) / 2.
      xx = r(8)
      ffc(i) = xx / (xx + exp(9.043 - .002135 * xx))
    end do
  end subroutine subbasin_initialise_weather_gen