SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
teb_irrig.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE teb_irrig(OIRRIG, PTSTEP, KMONTH, PSOLAR_TIME, &
7  pstart_month, pend_month, pstart_hour, pend_hour,&
8  p24h_irrig, pirrig )
9 ! ##########################################################################
10 !
11 !!**** *TEB_IRRIG*
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 ! Computes the amount of water for irrigation
17 !
18 !
19 !!** METHOD
20 ! ------
21 !
22 !
23 !! EXTERNAL
24 !! --------
25 !!
26 !!
27 !! IMPLICIT ARGUMENTS
28 !! ------------------
29 !!
30 !!
31 !! REFERENCE
32 !! ---------
33 !!
34 !!
35 !! AUTHOR
36 !! ------
37 !!
38 !! C. DeMunck & V. Masson * Meteo-France *
39 !!
40 !! MODIFICATIONS
41 !! -------------
42 !! Original 05/2013
43 !-------------------------------------------------------------------------------
44 !
45 !* 0. DECLARATIONS
46 ! ------------
47 !
48 USE yomhook ,ONLY : lhook, dr_hook
49 USE parkind1 ,ONLY : jprb
50 !
51 IMPLICIT NONE
52 !
53 !* 0.1 declarations of arguments
54 !
55 !
56 LOGICAL, INTENT(IN) :: oirrig ! Flag for irrigation or not
57 REAL, INTENT(IN) :: ptstep ! time step
58 INTEGER, INTENT(IN) :: kmonth ! Present Month
59 REAL, DIMENSION(:), INTENT(IN) :: psolar_time ! solar time (s since midnight)
60 REAL, DIMENSION(:), INTENT(IN) :: pstart_month! First month for irrigation (included)
61 REAL, DIMENSION(:), INTENT(IN) :: pend_month ! Last month for irrigation (included)
62 REAL, DIMENSION(:), INTENT(IN) :: pstart_hour ! First month for irrigation (included)
63 REAL, DIMENSION(:), INTENT(IN) :: pend_hour ! Last month for irrigation (ecluded)
64 REAL, DIMENSION(:), INTENT(IN) :: p24h_irrig ! 24h total irrigation
65 REAL, DIMENSION(:), INTENT(OUT) :: pirrig ! present irrigation
66 !
67 REAL(KIND=JPRB) :: zhook_handle
68 !
69 !* 0.2 declarations of local variables
70 !
71 LOGICAL, DIMENSION(SIZE(PIRRIG)):: gmonth!if irrigation occurs during present month
72 LOGICAL, DIMENSION(SIZE(PIRRIG)):: ghour !if irrigation occurs at present time
73 REAL, DIMENSION(SIZE(PIRRIG)):: zduration ! duration of irrigation per day (s)
74 !
75 !-------------------------------------------------------------------------------
76 IF (lhook) CALL dr_hook('TEB_IRRIG',0,zhook_handle)
77 !
78 !* 1. Default
79 ! -------
80 !
81 pirrig = 0.
82 !
83 IF (.NOT. oirrig) THEN
84  IF (lhook) CALL dr_hook('TEB_IRRIG',1,zhook_handle)
85  RETURN
86 END IF
87 !
88 !-------------------------------------------------------------------------------
89 !
90 !* 2. Is present month irrigated ?
91 ! ----------------------------
92 !
93 WHERE (pstart_month <= pend_month) ! for summer in North hemisphere
94  gmonth = kmonth>=pstart_month .AND. kmonth<= pend_month
95 ELSEWHERE ! for summer in South hemisphere
96  ! change of year during irrigation period
97  gmonth = kmonth>=pstart_month .OR. kmonth<= pend_month
98 END WHERE
99 !
100 !-------------------------------------------------------------------------------
101 !
102 !* 3. Is present time irrigated (for each location) ?
103 ! -----------------------------------------------
104 !
105 ghour = .false.
106 zduration = 0.
107 !
108 WHERE (pstart_hour <= pend_hour) ! typically irrigation during day
109  ghour = psolar_time+ptstep>=pstart_hour*3600. .AND. psolar_time<=pend_hour*3600.
110  zduration = 3600.* (pend_hour-pstart_hour)
111 ELSE WHERE ! typically irrigation during night
112  ! midnight is during irrigation period
113  ghour = psolar_time+ptstep>=pstart_hour*3600. .OR. psolar_time< pend_hour*3600.
114  zduration = 3600.* (pend_hour + 24.-pstart_hour)
115 END WHERE
116 !
117 !-------------------------------------------------------------------------------
118 !
119 !* 4. Computes irrigation
120 ! -------------------
121 !
122 !* if duration is very short, all water is irrigated during the timestep
123 zduration = max(zduration, ptstep)
124 !
125 !* Concentration of the total 24h irrigation during the period of irrigation
126 WHERE(gmonth(:) .AND. ghour(:)) pirrig(:) = p24h_irrig(:) / zduration(:)
127 !
128 !-------------------------------------------------------------------------------
129 IF (lhook) CALL dr_hook('TEB_IRRIG',1,zhook_handle)
130 !
131 !-------------------------------------------------------------------------------
132 !
133 END SUBROUTINE teb_irrig
subroutine teb_irrig(OIRRIG, PTSTEP, KMONTH, PSOLAR_TIME, PSTART_MONTH, PEND_MONTH, PSTART_HOUR, PEND_HOUR, P24H_IRRIG, PIRRIG)
Definition: teb_irrig.F90:6