SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_pgd_teb_irrign.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 writesurf_pgd_teb_irrig_n (DGU, U, &
7  tir, &
8  hprogram)
9 ! ################################################
10 !
11 !!**** *WRITESURF_PGD_TEB_IRRIG_n* - writes TEB irrigation physiographic fields
12 !!
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !!
31 !! AUTHOR
32 !! ------
33 !! V. Masson *Meteo France*
34 !!
35 !! MODIFICATIONS
36 !! -------------
37 !! Original 05/2013
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 !
44 !
45 !
46 !
48 USE modd_surf_atm_n, ONLY : surf_atm_t
49 !
50 USE modd_teb_irrig_n, ONLY : teb_irrig_t
51 !
53 !
54 !
55 USE yomhook ,ONLY : lhook, dr_hook
56 USE parkind1 ,ONLY : jprb
57 !
58 IMPLICIT NONE
59 !
60 !* 0.1 Declarations of arguments
61 ! -------------------------
62 !
63 !
64 !
65 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
66 TYPE(surf_atm_t), INTENT(INOUT) :: u
67 !
68 TYPE(teb_irrig_t), INTENT(INOUT) :: tir
69 !
70  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
71 !
72 !* 0.2 Declarations of local variables
73 ! -------------------------------
74 !
75 INTEGER :: iresp ! IRESP : return-code if a problem appears
76  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
77  CHARACTER(LEN=100):: ycomment ! Comment string
78 INTEGER :: jlayer ! loop index
79 INTEGER :: jtime ! loop index
80 REAL, DIMENSION(:), ALLOCATABLE :: zwork
81 REAL(KIND=JPRB) :: zhook_handle
82 !
83 !-------------------------------------------------------------------------------
84 !
85 IF (lhook) CALL dr_hook('WRITESURF_PGD_TEB_IRRIG_n',0,zhook_handle)
86 !
87 ! Flag for irrigation of gardens
88 yrecfm='L_PAR_GD_IRR'
89 ycomment='FLAG FOR SPECIFIED GARDEN IRRIGATION PARAMETERS'
90  CALL write_surf(dgu, u, &
91  hprogram,yrecfm,tir%LPAR_GD_IRRIG,iresp,hcomment=ycomment)
92 !
93 ! Parameters describing irrigation
94 IF (tir%LPAR_GD_IRRIG) THEN
95 !
96  yrecfm='D_GD_SM_IRR'
97  ycomment='Start Month for Gardens Irrigation'
98  CALL write_surf(dgu, u, &
99  hprogram,yrecfm,tir%XGD_START_MONTH(:),iresp,hcomment=ycomment)
100 !
101  yrecfm='D_GD_EM_IRR'
102  ycomment='End Month for Gardens Irrigation'
103  CALL write_surf(dgu, u, &
104  hprogram,yrecfm,tir%XGD_END_MONTH (:),iresp,hcomment=ycomment)
105 !
106  yrecfm='D_GD_SH_IRR'
107  ycomment='Start Hour for Gardens Irrigation'
108  CALL write_surf(dgu, u, &
109  hprogram,yrecfm,tir%XGD_START_HOUR (:),iresp,hcomment=ycomment)
110 !
111  yrecfm='D_GD_EH_IRR'
112  ycomment='End Hour for Gardens Irrigation'
113  CALL write_surf(dgu, u, &
114  hprogram,yrecfm,tir%XGD_END_HOUR (:),iresp,hcomment=ycomment)
115 !
116  yrecfm='D_GD_IRRIG'
117  ycomment='24h mean Irrigation rate for Gardens Irrigation'
118  CALL write_surf(dgu, u, &
119  hprogram,yrecfm,tir%XGD_24H_IRRIG (:),iresp,hcomment=ycomment)
120 !
121 ENDIF
122 !
123 ! Flag for irrigation of greenroofs
124 yrecfm='L_PAR_GR_IRR'
125 ycomment='FLAG FOR SPECIFIED GREENROOFS IRRIGATION PARAMETERS'
126  CALL write_surf(dgu, u, &
127  hprogram,yrecfm,tir%LPAR_GR_IRRIG,iresp,hcomment=ycomment)
128 !
129 ! Parameters describing irrigation
130 IF (tir%LPAR_GR_IRRIG) THEN
131 !
132  yrecfm='D_GR_SM_IRR'
133  ycomment='Start Month for Greenroofs Irrigation'
134  CALL write_surf(dgu, u, &
135  hprogram,yrecfm,tir%XGR_START_MONTH(:),iresp,hcomment=ycomment)
136 !
137  yrecfm='D_GR_EM_IRR'
138  ycomment='End Month for Greenroofs Irrigation'
139  CALL write_surf(dgu, u, &
140  hprogram,yrecfm,tir%XGR_END_MONTH (:),iresp,hcomment=ycomment)
141 !
142  yrecfm='D_GR_SH_IRR'
143  ycomment='Start Hour for Greenroofs Irrigation'
144  CALL write_surf(dgu, u, &
145  hprogram,yrecfm,tir%XGR_START_HOUR (:),iresp,hcomment=ycomment)
146 !
147  yrecfm='D_GR_EH_IRR'
148  ycomment='End Hour for Greenroofs Irrigation'
149  CALL write_surf(dgu, u, &
150  hprogram,yrecfm,tir%XGR_END_HOUR (:),iresp,hcomment=ycomment)
151 !
152  yrecfm='D_GR_IRRIG'
153  ycomment='24h mean Irrigation rate for Greenroofs Irrigation'
154  CALL write_surf(dgu, u, &
155  hprogram,yrecfm,tir%XGR_24H_IRRIG (:),iresp,hcomment=ycomment)
156 !
157 ENDIF
158 !
159 ! Flag for watering of greenroofs
160 yrecfm='L_PAR_RD_IRR'
161 ycomment='FLAG FOR SPECIFIED ROAD IRRIGATION PARAMETERS'
162  CALL write_surf(dgu, u, &
163  hprogram,yrecfm,tir%LPAR_RD_IRRIG,iresp,hcomment=ycomment)
164 !
165 ! Parameters describing watering
166 IF (tir%LPAR_RD_IRRIG) THEN
167 !
168  yrecfm='D_RD_SM_IRR'
169  ycomment='Start Month for Roads Irrigation'
170  CALL write_surf(dgu, u, &
171  hprogram,yrecfm,tir%XRD_START_MONTH(:),iresp,hcomment=ycomment)
172 !
173  yrecfm='D_RD_EM_IRR'
174  ycomment='End Month for Roads Irrigation'
175  CALL write_surf(dgu, u, &
176  hprogram,yrecfm,tir%XRD_END_MONTH (:),iresp,hcomment=ycomment)
177 !
178  yrecfm='D_RD_SH_IRR'
179  ycomment='Start Hour for Roads Irrigation'
180  CALL write_surf(dgu, u, &
181  hprogram,yrecfm,tir%XRD_START_HOUR (:),iresp,hcomment=ycomment)
182 !
183  yrecfm='D_RD_EH_IRR'
184  ycomment='End Hour for Roads Irrigation'
185  CALL write_surf(dgu, u, &
186  hprogram,yrecfm,tir%XRD_END_HOUR (:),iresp,hcomment=ycomment)
187 !
188  yrecfm='D_RD_IRRIG'
189  ycomment='24h mean Irrigation rate for Roads Irrigation'
190  CALL write_surf(dgu, u, &
191  hprogram,yrecfm,tir%XRD_24H_IRRIG (:),iresp,hcomment=ycomment)
192 !
193 ENDIF
194 !
195 IF (lhook) CALL dr_hook('WRITESURF_PGD_TEB_IRRIG_n',1,zhook_handle)
196 !
197 !-------------------------------------------------------------------------------
198 !
199 END SUBROUTINE writesurf_pgd_teb_irrig_n
subroutine writesurf_pgd_teb_irrig_n(DGU, U, TIR, HPROGRAM)