ComputeSpatialAverageMeteo Subroutine

public subroutine ComputeSpatialAverageMeteo(dt, temp, tmean, tmax, tmin, precipitation, rh, radiation, netradiation, windspeed, daily_precipitation, irrigation)

Compute spatial average of meteorological variables

Arguments

Type IntentOptional Attributes Name
integer(kind=short), intent(in) :: dt

time step (s)

type(grid_real), intent(in) :: temp

air temperarure (°C)

type(grid_real), intent(in) :: tmean

air temperarure daily mean(°C)

type(grid_real), intent(in) :: tmax

air temperarure daily max (°C)

type(grid_real), intent(in) :: tmin

air temperarure daily min (°C)

type(grid_real), intent(in) :: precipitation

precipitation rate (m/s)

type(grid_real), intent(in) :: rh

air relative humidity (0-100)

type(grid_real), intent(in) :: radiation

solar radiation (w/m2)

type(grid_real), intent(in) :: netradiation

net radiation (w/m2)

type(grid_real), intent(in) :: windspeed

wind speed (m/s)

type(grid_real), intent(in) :: daily_precipitation

daily precipitation (m/s)

type(grid_real), intent(in) :: irrigation

irrigation rate (m/s)


Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: count
integer(kind=short), public :: i

Source Code

SUBROUTINE ComputeSpatialAverageMeteo   & 
!
 (dt, temp, tmean, tmax, tmin, precipitation, rh, radiation, netradiation,  &
    windspeed, daily_precipitation, irrigation)  

IMPLICIT NONE

!arguments with intent in:
INTEGER (KIND = short), INTENT(IN) :: dt !!time step (s)  
TYPE (grid_real), INTENT(IN) :: temp !!air temperarure (°C)
TYPE (grid_real), INTENT(IN) :: tmean !!air temperarure daily mean(°C)
TYPE (grid_real), INTENT(IN) :: tmax !!air temperarure daily max (°C)
TYPE (grid_real), INTENT(IN) :: tmin !!air temperarure daily min (°C)
TYPE (grid_real), INTENT(IN) :: precipitation !!precipitation rate (m/s)
TYPE (grid_real), INTENT(IN) :: rh !!air relative humidity (0-100)
TYPE (grid_real), INTENT(IN) :: radiation !!solar radiation (w/m2)
TYPE (grid_real), INTENT(IN) :: netradiation !!net radiation (w/m2)
TYPE (grid_real), INTENT(IN) :: windspeed !!wind speed (m/s)
TYPE (grid_real), INTENT(IN) :: daily_precipitation !!daily precipitation (m/s)
TYPE (grid_real), INTENT(IN) :: irrigation !!irrigation rate (m/s)


!local declarations
INTEGER (KIND = short) :: i
INTEGER (KIND = short) :: count
!-------------------------------end of declaration-----------------------------

DO i = 1, nextents
    count = 0
    !precipitation
    IF ( meteoout (1) ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (precipitation,  maskInteger = extents (i) % mask ) * &
            dt * 1000. !conversion to mm over dt
    END IF
    
    !daily precipitation
    IF ( meteoout (2) ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (daily_precipitation,  maskInteger = extents (i) % mask ) * &
            dt * 1000. !conversion to mm over dt
    END IF
    
    !temperature
    IF ( meteoout (3) ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (temp,  maskInteger = extents (i) % mask ) 
    END IF

    !temperature daily mean
    IF ( meteoout (4) ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (tmean,  maskInteger = extents (i) % mask ) 
    END IF

    !temperature daily max
    IF ( meteoout (5)  ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (tmax,  maskInteger = extents (i) % mask ) 
    END IF

    !temperature daily min
    IF ( meteoout (6) ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (tmin,  maskInteger = extents (i) % mask ) 
    END IF

    !relative humidity
    IF ( meteoout (7) ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (rh,  maskInteger = extents (i) % mask ) 
    END IF

    !radiation
    IF ( meteoout (8) ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (radiation,  maskInteger = extents (i) % mask ) 
    END IF
    
    !net radiation
    IF ( meteoout (9) ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (netradiation,  maskInteger = extents (i) % mask ) 
    END IF

    !windspeed
    IF ( meteoout (10) ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (windspeed,  maskInteger = extents (i) % mask ) 
    END IF
    
    !irrigation
    IF ( meteoout (11) ) THEN
      count = count + 1
      extents (i) % meteo (count) = &
            GetMean (irrigation,  maskInteger = extents (i) % mask ) * &
            dt * 1000. !conversion to mm over dt
    END IF

    
            
END DO

RETURN
END SUBROUTINE ComputeSpatialAverageMeteo