subroutine crop_process(j, je, k, n, wet, additionalGwUptake, avt, bWAM_Module, dart, daycounter, es, fc, flu, frar, humi, ida, iy, iyr, mstruc, nbyr, nn, nveg, pit, ra, sbar, sep, ste, tmn, tx, uap, ylc, yls, z, bSnowModule, tmit)
!**** PURPOSE: THIS SUBROUTINE CALCULATES DAILY POTENTIAL & ACTUAL GROWTH
! OF TOTAL PLANT BIOMASS AND ROOTS AND CALCULATES LEAF AREA INDEX.
! IT ADJUSTS DAILY BIOMASS TO WATER, TEMP. & NUTR. STRESS.
!**** CALLED IN: HYDROTOP
!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
! PARAMETERS & VARIABLES
!
! >>>>> COMMON PARAMETERS & VARIABLES
! actual = actual evapotranspiration, mm
! alai(j, je) = leaf area index
! cva(j, je) = vegetation cover, kg/ha
! dm(j, je) = total biomass, kg/ha
! ep = plant transpiration, mm
! es = soil evaporation, mm
! g(j, je) = fraction of heat units to maturity accumulated
! icrop = switch code to print from crop()
! icrsb = number of subbasin to print from crop(), if icrop = 1
! icrso = number of soil to print from crop(), if icrop = 1
! ida = current day
! igro(j, je) = vegetation index, =1 if vegetation is growing
! rd(j, je) = root depth, mm
! rsd(j, je, 2)= crop residue in two upper soil layers, kg/ha
! ts = temperature stress factor
! uap = P uptake in hydrotope, kg/ha
! ws(j, je) = water stress factor
! >>>>>
!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
!**** Include common parameters
use vegetation, only : vegetation_water_stress, olai, dm, ws, rsd, rd, g, alai, ts, ep
real(dp), dimension(:), intent(inout) :: additionalGwUptake
real(dp), dimension(:), intent(in) :: avt
logical, intent(in) :: bWAM_Module
real(dp), dimension(:), intent(in) :: dart
integer, intent(in) :: daycounter
real(dp), intent(in) :: es
real(dp), dimension(:, :), intent(in) :: fc
real(dp), dimension(:), intent(in) :: flu
real(dp), dimension(:, :), intent(in) :: frar
real(dp), dimension(:), intent(in) :: humi
integer, intent(in) :: ida
integer, intent(in) :: iy
integer, intent(in) :: iyr
integer, dimension(:, :, :), intent(in) :: mstruc
integer, intent(in) :: nbyr
integer, intent(in) :: nn
integer, dimension(:, :), intent(in) :: nveg
real(dp), intent(in) :: pit
real(dp), dimension(:), intent(in) :: ra
real(dp), dimension(:), intent(in) :: sbar
real(dp), intent(inout) :: sep
real(dp), dimension(:, :, :), intent(inout) :: ste
real(dp), dimension(:), intent(in) :: tmn
real(dp), dimension(:), intent(in) :: tx
real(dp), intent(out) :: uap
real(dp), dimension(:), intent(in) :: ylc
real(dp), dimension(:), intent(in) :: yls
real(dp), dimension(:, :), intent(in) :: z
logical, intent(in) :: bSnowModule
real(dp), intent(in) :: tmit
integer j, je, n, k, wet
uap = 0.
ts = 0.
!**** CALC vegetation cover
cva(j, je) = .8 * dm(j, je) + rsd(j, je, 1)
!#### CALL OPERAT
call crop_operation(j, je, k, alai, dm, frar, g, ida, iy, olai, rd, rsd, ws)
!#### CALL WSTRESS to COMPUTE WATER STRESS
if (igro(j, je) .ge. 1) call vegetation_water_stress(j, je, k, n, wet, additionalGwUptake, bWAM_Module, dart, daycounter, fc, frar, humi, icc, ida, iy, iyr, mstruc, nbyr, nn, nucr, nveg, rdmx, sbar, sep, ste, z)
actual = ep + es
!#### CALL GROWTH
call crop_growth(avt, bSnowModule, flu, frar, ida, j, je, n, nn, nveg, pit, ra, tmit, tmn, tx, ylc, yls)
return
end subroutine crop_process