1 | !! This subroutine is the interface between the main program |
---|
2 | !! (LMDZ or dim2_driver) and SECHIBA. |
---|
3 | !! - Input fields are gathered to keep just continental points |
---|
4 | !! - call sechiba_main That's SECHIBA process. |
---|
5 | !! - Output fields are scattered to complete global fields |
---|
6 | !! |
---|
7 | !! @call sechiba_main |
---|
8 | !! @Version : $Revision$, $Date$ |
---|
9 | !! |
---|
10 | !! @author Marie-Alice Foujols and Jan Polcher |
---|
11 | !! |
---|
12 | !< $HeadURL$ |
---|
13 | !< $Date$ |
---|
14 | !< $Author$ |
---|
15 | !< $Revision$ |
---|
16 | !! IPSL (2006) |
---|
17 | !! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC |
---|
18 | !! |
---|
19 | !f90doc MODULEintersurf |
---|
20 | MODULE intersurf |
---|
21 | |
---|
22 | USE IOIPSL |
---|
23 | USE xios_orchidee |
---|
24 | USE ioipsl_para |
---|
25 | USE defprec |
---|
26 | USE sechiba |
---|
27 | USE constantes |
---|
28 | USE constantes_soil |
---|
29 | USE control |
---|
30 | USE pft_parameters |
---|
31 | USE mod_orchidee_para |
---|
32 | USE solar |
---|
33 | USE grid |
---|
34 | USE Orch_Write_field_p |
---|
35 | USE thermosoilc, ONLY : thermosoilc_levels |
---|
36 | USE ioipslctrl, ONLY : ioipslctrl_history, ioipslctrl_restini, ok_histsync, max_hist_level, dw |
---|
37 | |
---|
38 | IMPLICIT NONE |
---|
39 | |
---|
40 | PRIVATE |
---|
41 | PUBLIC :: Init_intersurf, intersurf_main, intersurf_main_2d, intersurf_main_gathered, intsurf_time |
---|
42 | PUBLIC :: intersurf_initialize_2d, intersurf_initialize_gathered |
---|
43 | |
---|
44 | |
---|
45 | ! Interface called from LMDZ |
---|
46 | INTERFACE intersurf_main |
---|
47 | MODULE PROCEDURE intersurf_main_gathered |
---|
48 | END INTERFACE |
---|
49 | |
---|
50 | ! |
---|
51 | ! Global variables |
---|
52 | ! |
---|
53 | ! |
---|
54 | LOGICAL, SAVE :: l_first_intersurf=.TRUE.!! Initialisation has to be done one time |
---|
55 | !$OMP THREADPRIVATE(l_first_intersurf) |
---|
56 | INTEGER(i_std), SAVE :: printlev_loc !! Write level to this module |
---|
57 | !$OMP THREADPRIVATE(printlev_loc) |
---|
58 | INTEGER(i_std), SAVE :: hist_id, rest_id !! IDs for history and restart files |
---|
59 | !$OMP THREADPRIVATE(hist_id, rest_id) |
---|
60 | INTEGER(i_std), SAVE :: hist2_id !! ID for the second history files (Hi-frequency ?) |
---|
61 | !$OMP THREADPRIVATE(hist2_id) |
---|
62 | INTEGER(i_std), SAVE :: hist_id_stom, hist_id_stom_IPCC, rest_id_stom !! Dito for STOMATE |
---|
63 | !$OMP THREADPRIVATE(hist_id_stom, hist_id_stom_IPCC, rest_id_stom) |
---|
64 | ! |
---|
65 | INTEGER(i_std), SAVE :: itau_offset !! This offset is used to phase the |
---|
66 | ! !! calendar of the GCM or the driver. |
---|
67 | !$OMP THREADPRIVATE(itau_offset) |
---|
68 | REAL(r_std), SAVE :: date0_shifted |
---|
69 | !$OMP THREADPRIVATE(date0_shifted) |
---|
70 | ! |
---|
71 | !! first day of this year |
---|
72 | REAL(r_std), SAVE :: julian0 |
---|
73 | !$OMP THREADPRIVATE(julian0) |
---|
74 | ! |
---|
75 | LOGICAL, PARAMETER :: check_INPUTS = .false. !! (very) long print of INPUTs in intersurf |
---|
76 | |
---|
77 | LOGICAL, SAVE :: ok_q2m_t2m=.TRUE. !! Flag ok if the variables are present in the call in gcm. |
---|
78 | !$OMP THREADPRIVATE(ok_q2m_t2m) |
---|
79 | LOGICAL, SAVE :: fatmco2 !! Flag to force the value of atmospheric CO2 for vegetation. |
---|
80 | !$OMP THREADPRIVATE(fatmco2) |
---|
81 | REAL(r_std), SAVE :: atmco2 !! atmospheric CO2 |
---|
82 | !$OMP THREADPRIVATE(atmco2) |
---|
83 | INTEGER(i_std), SAVE :: nb_fields_in=-1 !! Number of fields to give to the GCM |
---|
84 | !$OMP THREADPRIVATE(nb_fields_in) |
---|
85 | INTEGER(i_std), SAVE :: nb_fields_out=-1 !! Number of fields to get from the GCM |
---|
86 | !$OMP THREADPRIVATE(nb_fields_out) |
---|
87 | |
---|
88 | PUBLIC l_first_intersurf |
---|
89 | |
---|
90 | CONTAINS |
---|
91 | |
---|
92 | !! ============================================================================================================================= |
---|
93 | !! SUBROUTINE: intersurf_initialize_2d |
---|
94 | !! |
---|
95 | !>\BRIEF Initialization and call to sechiba_initialize |
---|
96 | !! |
---|
97 | !! DESCRIPTION: Initialization of module variables, read options from parameter file, initialize output files and call to |
---|
98 | !! sechiba_initialize. |
---|
99 | !! |
---|
100 | !! This subroutine is called from dim2_driver before the first call to intersurf_main_2d. |
---|
101 | !! |
---|
102 | !! \n |
---|
103 | !_ ============================================================================================================================== |
---|
104 | |
---|
105 | SUBROUTINE intersurf_initialize_2d (kjit, iim, jjm, kjpindex, kindex, xrdt, & |
---|
106 | lrestart_read, lrestart_write, lon, lat, zcontfrac, zresolution, date0, & |
---|
107 | zlev, u, v, qair, temp_air, epot_air, ccanopy, & |
---|
108 | cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
109 | precip_rain, precip_snow, lwdown, swnet, swdown, pb, & |
---|
110 | vevapp, fluxsens, fluxlat, coastalflow, riverflow, & |
---|
111 | tsol_rad, temp_sol_new, qsurf, albedo, emis, z0) |
---|
112 | |
---|
113 | IMPLICIT NONE |
---|
114 | |
---|
115 | !! 0. Variable and parameter declaration |
---|
116 | !! 0.1 Input variables |
---|
117 | INTEGER(i_std),INTENT (in) :: kjit !! Time step number |
---|
118 | INTEGER(i_std),INTENT (in) :: iim, jjm !! Dimension of input fields |
---|
119 | INTEGER(i_std),INTENT (in) :: kjpindex !! Number of continental points |
---|
120 | REAL(r_std),INTENT (in) :: xrdt !! Time step in seconds |
---|
121 | LOGICAL, INTENT (in) :: lrestart_read !! Logical for _restart_ file to read |
---|
122 | LOGICAL, INTENT (in) :: lrestart_write !! Logical for _restart_ file to write' |
---|
123 | REAL(r_std), INTENT (in) :: date0 !! Date at which kjit = 0 |
---|
124 | INTEGER(i_std),DIMENSION (kjpindex), INTENT (in) :: kindex !! Index for continental points |
---|
125 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: u !! Lowest level wind speed |
---|
126 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: v !! Lowest level wind speed |
---|
127 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: zlev !! Height of first layer |
---|
128 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: qair !! Lowest level specific humidity |
---|
129 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: precip_rain !! Rain precipitation |
---|
130 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: precip_snow !! Snow precipitation |
---|
131 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: lwdown !! Down-welling long-wave flux |
---|
132 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: swnet !! Net surface short-wave flux |
---|
133 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: swdown !! Downwelling surface short-wave flux |
---|
134 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: temp_air !! Air temperature in Kelvin |
---|
135 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: epot_air !! Air potential energy |
---|
136 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: ccanopy !! CO2 concentration in the canopy |
---|
137 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: petAcoef !! Coeficients A from the PBL resolution |
---|
138 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: peqAcoef !! One for T and another for q |
---|
139 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: petBcoef !! Coeficients B from the PBL resolution |
---|
140 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: peqBcoef !! One for T and another for q |
---|
141 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: pb !! Surface pressure |
---|
142 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: lon, lat !! Geographical coordinates |
---|
143 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: zcontfrac !! Fraction of continent in the grid |
---|
144 | REAL(r_std),DIMENSION (iim,jjm,2), INTENT(in) :: zresolution !! resolution in x and y dimensions |
---|
145 | |
---|
146 | !! 0.2 Output variables |
---|
147 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: z0 !! Surface roughness |
---|
148 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: coastalflow !! Diffuse flow of water into the ocean (m^3/dt) |
---|
149 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: riverflow !! Largest rivers flowing into the ocean (m^3/dt) |
---|
150 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: tsol_rad !! Radiative surface temperature |
---|
151 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: vevapp !! Total of evaporation |
---|
152 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: temp_sol_new !! New soil temperature |
---|
153 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: qsurf !! Surface specific humidity |
---|
154 | REAL(r_std),DIMENSION (iim,jjm,2), INTENT(out) :: albedo !! Albedo |
---|
155 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: fluxsens !! Sensible chaleur flux |
---|
156 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: fluxlat !! Latent chaleur flux |
---|
157 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: emis !! Emissivity |
---|
158 | |
---|
159 | !! 0.3 Modified variables |
---|
160 | REAL(r_std),DIMENSION (iim,jjm), INTENT(inout) :: cdrag !! Cdrag |
---|
161 | |
---|
162 | !! 0.4 Local variables |
---|
163 | REAL(r_std),DIMENSION (kjpindex) :: zu !! Work array to keep u |
---|
164 | REAL(r_std),DIMENSION (kjpindex) :: zv !! Work array to keep v |
---|
165 | REAL(r_std),DIMENSION (kjpindex) :: zzlev !! Work array to keep zlev |
---|
166 | REAL(r_std),DIMENSION (kjpindex) :: zqair !! Work array to keep qair |
---|
167 | REAL(r_std),DIMENSION (kjpindex) :: zprecip_rain !! Work array to keep precip_rain |
---|
168 | REAL(r_std),DIMENSION (kjpindex) :: zprecip_snow !! Work array to keep precip_snow |
---|
169 | REAL(r_std),DIMENSION (kjpindex) :: zlwdown !! Work array to keep lwdown |
---|
170 | REAL(r_std),DIMENSION (kjpindex) :: zswnet !! Work array to keep swnet |
---|
171 | REAL(r_std),DIMENSION (kjpindex) :: zswdown !! Work array to keep swdown |
---|
172 | REAL(r_std),DIMENSION (kjpindex) :: ztemp_air !! Work array to keep temp_air |
---|
173 | REAL(r_std),DIMENSION (kjpindex) :: zepot_air !! Work array to keep epot_air |
---|
174 | REAL(r_std),DIMENSION (kjpindex) :: zccanopy !! Work array to keep ccanopy |
---|
175 | REAL(r_std),DIMENSION (kjpindex) :: zpetAcoef !! Work array to keep petAcoef |
---|
176 | REAL(r_std),DIMENSION (kjpindex) :: zpeqAcoef !! Work array to keep peqAcoef |
---|
177 | REAL(r_std),DIMENSION (kjpindex) :: zpetBcoef !! Work array to keep petBcoef |
---|
178 | REAL(r_std),DIMENSION (kjpindex) :: zpeqBcoef !! Work array to keep peqVcoef |
---|
179 | REAL(r_std),DIMENSION (kjpindex) :: zcdrag !! Work array to keep cdrag |
---|
180 | REAL(r_std),DIMENSION (kjpindex) :: zpb !! Work array to keep pb |
---|
181 | REAL(r_std),DIMENSION (kjpindex) :: zz0 !! Work array to keep z0 |
---|
182 | REAL(r_std),DIMENSION (kjpindex) :: zcoastal !! Work array to keep coastalflow |
---|
183 | REAL(r_std),DIMENSION (kjpindex) :: zriver !! Work array to keep riverflow |
---|
184 | REAL(r_std),DIMENSION (kjpindex) :: znetco2 !! Work array to keep netco2flux |
---|
185 | REAL(r_std),DIMENSION (kjpindex) :: zcarblu !! Work array to keep fco2_land_use |
---|
186 | REAL(r_std),DIMENSION (kjpindex) :: ztsol_rad !! Work array to keep tsol_rad |
---|
187 | REAL(r_std),DIMENSION (kjpindex) :: zvevapp !! Work array to keep vevapp |
---|
188 | REAL(r_std),DIMENSION (kjpindex) :: ztemp_sol_new !! Work array to keep temp_sol_new |
---|
189 | REAL(r_std),DIMENSION (kjpindex) :: zqsurf !! Work array to keep qsurf |
---|
190 | REAL(r_std),DIMENSION (kjpindex,2) :: zalbedo !! Work array to keep albedo |
---|
191 | REAL(r_std),DIMENSION (kjpindex) :: zfluxsens !! Work array to keep fluxsens |
---|
192 | REAL(r_std),DIMENSION (kjpindex) :: zfluxlat !! Work array to keep fluxlat |
---|
193 | REAL(r_std),DIMENSION (kjpindex) :: zemis !! Work array to keep emis |
---|
194 | REAL(r_std),ALLOCATABLE, DIMENSION (:) :: soilth_lev !! Vertical soil axis for thermal scheme (m) |
---|
195 | INTEGER(i_std) :: i, j, ik |
---|
196 | INTEGER(i_std) :: ier |
---|
197 | INTEGER(i_std) :: itau_sechiba |
---|
198 | REAL(r_std) :: zlev_mean |
---|
199 | INTEGER :: old_fileout !! old Logical Int for std IO output |
---|
200 | |
---|
201 | |
---|
202 | CALL ipslnlf_p(new_number=numout,old_number=old_fileout) |
---|
203 | ! |
---|
204 | ! Configuration of SSL specific parameters |
---|
205 | ! |
---|
206 | CALL control_initialize(xrdt) |
---|
207 | |
---|
208 | CALL intsurf_time( kjit, date0) |
---|
209 | |
---|
210 | ! Initialize specific write level |
---|
211 | printlev_loc=get_printlev('instersurf') |
---|
212 | |
---|
213 | IF ( printlev_loc >=1 ) WRITE(numout,*) 'Initialisation of intersurf_main_2d' |
---|
214 | OFF_LINE_MODE = .TRUE. |
---|
215 | |
---|
216 | DO ik=1,kjpindex |
---|
217 | |
---|
218 | j = ((kindex(ik)-1)/iim) + 1 |
---|
219 | i = (kindex(ik) - (j-1)*iim) |
---|
220 | |
---|
221 | !- Create the internal coordinate table |
---|
222 | !- |
---|
223 | lalo(ik,1) = lat(i,j) |
---|
224 | lalo(ik,2) = lon(i,j) |
---|
225 | ! |
---|
226 | !- Store the fraction of the continents only once so that the user |
---|
227 | !- does not change them afterwards. |
---|
228 | !- |
---|
229 | contfrac(ik) = zcontfrac(i,j) |
---|
230 | ENDDO |
---|
231 | CALL gather(contfrac,contfrac_g) |
---|
232 | CALL gather(lalo,lalo_g) |
---|
233 | CALL gather2D_mpi(lon,lon_g) |
---|
234 | CALL gather2D_mpi(lat,lat_g) |
---|
235 | CALL gather2D_mpi(zlev,zlev_g) |
---|
236 | |
---|
237 | CALL ioipslctrl_restini(kjit, date0, xrdt, rest_id, rest_id_stom, itau_offset, date0_shifted) |
---|
238 | itau_sechiba = kjit + itau_offset |
---|
239 | |
---|
240 | !!- Initialize module for output with XIOS |
---|
241 | ! |
---|
242 | ! Get the vertical soil levels for the thermal scheme, to be used in xios_orchidee_init |
---|
243 | ! Get the vertical soil levels for the thermal scheme, to be used in xios_orchidee_init |
---|
244 | ALLOCATE(soilth_lev(ngrnd), stat=ier) |
---|
245 | IF (ier /= 0) THEN |
---|
246 | CALL ipslerr_p(3,'intersurf_main_2d', 'Error in allocation of soilth_lev','','') |
---|
247 | END IF |
---|
248 | IF (hydrol_cwrr) THEN |
---|
249 | soilth_lev(1:ngrnd) = znt(:) |
---|
250 | ELSE |
---|
251 | soilth_lev(1:ngrnd) = thermosoilc_levels() |
---|
252 | END IF |
---|
253 | |
---|
254 | CALL xios_orchidee_init( MPI_COMM_ORCH, & |
---|
255 | date0, year, month, day, & |
---|
256 | lon, lat, soilth_lev ) |
---|
257 | |
---|
258 | !- Initialize IOIPSL sechiba output files |
---|
259 | CALL ioipslctrl_history(iim, jjm, lon, lat, kindex, kjpindex, itau_sechiba, date0_shifted, xrdt, hist_id, & |
---|
260 | hist2_id, hist_id_stom, hist_id_stom_IPCC) |
---|
261 | |
---|
262 | IF ( printlev_loc>=3 ) WRITE(numout,*) 'End of Initialisation of intersurf' |
---|
263 | ! |
---|
264 | ! Shift the time step to phase the two models |
---|
265 | ! |
---|
266 | itau_sechiba = kjit + itau_offset |
---|
267 | |
---|
268 | ! Update the calendar in xios by sending the new time step |
---|
269 | ! Special case : the model is only in initialization phase and the current itau_sechiba is not a real time step. |
---|
270 | ! Therefor give itau_sechiba+1 to xios to have a correct time axis in output files. |
---|
271 | CALL xios_orchidee_update_calendar(itau_sechiba+1) |
---|
272 | |
---|
273 | CALL intsurf_time( itau_sechiba, date0_shifted ) |
---|
274 | ! |
---|
275 | ! 1. gather input fields from kindex array |
---|
276 | ! Warning : I'm not sure this interface with one dimension array is the good one |
---|
277 | ! |
---|
278 | DO ik=1, kjpindex |
---|
279 | |
---|
280 | j = ((kindex(ik)-1)/iim) + 1 |
---|
281 | i = (kindex(ik) - (j-1)*iim) |
---|
282 | |
---|
283 | zu(ik) = u(i,j) |
---|
284 | zv(ik) = v(i,j) |
---|
285 | zzlev(ik) = zlev(i,j) |
---|
286 | zqair(ik) = qair(i,j) |
---|
287 | zprecip_rain(ik) = precip_rain(i,j)*xrdt |
---|
288 | zprecip_snow(ik) = precip_snow(i,j)*xrdt |
---|
289 | zlwdown(ik) = lwdown(i,j) |
---|
290 | zswnet(ik) = swnet(i,j) |
---|
291 | zswdown(ik) = swdown(i,j) |
---|
292 | ztemp_air(ik) = temp_air(i,j) |
---|
293 | zepot_air(ik) = epot_air(i,j) |
---|
294 | zccanopy(ik) = ccanopy(i,j) |
---|
295 | zpetAcoef(ik) = petAcoef(i,j) |
---|
296 | zpeqAcoef(ik) = peqAcoef(i,j) |
---|
297 | zpetBcoef(ik) = petBcoef(i,j) |
---|
298 | zpeqBcoef(ik) = peqBcoef(i,j) |
---|
299 | zcdrag(ik) = cdrag(i,j) |
---|
300 | zpb(ik) = pb(i,j) |
---|
301 | |
---|
302 | ENDDO |
---|
303 | ! |
---|
304 | IF (check_INPUTS) THEN |
---|
305 | WRITE(numout,*) "Intersurf_main_2D :" |
---|
306 | WRITE(numout,*) "Time step number = ",kjit |
---|
307 | WRITE(numout,*) "Dimension of input fields = ",iim, jjm |
---|
308 | WRITE(numout,*) "Number of continental points = ",kjpindex |
---|
309 | WRITE(numout,*) "Time step in seconds = ",xrdt |
---|
310 | WRITE(numout,*) "Logical for _restart_ file to read, write = ",lrestart_read,lrestart_write |
---|
311 | WRITE(numout,*) "Date at which kjit = 0 = ",date0 |
---|
312 | WRITE(numout,*) "Index for continental points = ",kindex |
---|
313 | WRITE(numout,*) "Lowest level wind speed North = ",zu |
---|
314 | WRITE(numout,*) "Lowest level wind speed East = ",zv |
---|
315 | WRITE(numout,*) "Height of first layer = ",zzlev |
---|
316 | WRITE(numout,*) "Lowest level specific humidity = ",zqair |
---|
317 | WRITE(numout,*) "Rain precipitation = ",zprecip_rain |
---|
318 | WRITE(numout,*) "Snow precipitation = ",zprecip_snow |
---|
319 | WRITE(numout,*) "Down-welling long-wave flux = ",zlwdown |
---|
320 | WRITE(numout,*) "Net surface short-wave flux = ",zswnet |
---|
321 | WRITE(numout,*) "Downwelling surface short-wave flux = ",zswdown |
---|
322 | WRITE(numout,*) "Air temperature in Kelvin = ",ztemp_air |
---|
323 | WRITE(numout,*) "Air potential energy = ",zepot_air |
---|
324 | WRITE(numout,*) "CO2 concentration in the canopy = ",zccanopy |
---|
325 | WRITE(numout,*) "Coeficients A from the PBL resolution = ",zpetAcoef |
---|
326 | WRITE(numout,*) "One for T and another for q = ",zpeqAcoef |
---|
327 | WRITE(numout,*) "Coeficients B from the PBL resolution = ",zpetBcoef |
---|
328 | WRITE(numout,*) "One for T and another for q = ",zpeqBcoef |
---|
329 | WRITE(numout,*) "Cdrag = ",zcdrag |
---|
330 | WRITE(numout,*) "Surface pressure = ",zpb |
---|
331 | WRITE(numout,*) "Geographical coordinates lon = ", (/ ( lon(ilandindex(ik), jlandindex(ik)), ik=1,kjpindex ) /) |
---|
332 | WRITE(numout,*) "Geographical coordinates lat = ", (/ ( lat(ilandindex(ik), jlandindex(ik)), ik=1,kjpindex ) /) |
---|
333 | WRITE(numout,*) "Fraction of continent in the grid = ",contfrac |
---|
334 | ENDIF |
---|
335 | ! |
---|
336 | ! 2. save the grid |
---|
337 | ! |
---|
338 | IF ( printlev_loc>=3 ) WRITE(numout,*) 'Save the grid' |
---|
339 | CALL histwrite_p(hist_id, 'LandPoints', itau_sechiba+1, (/ ( REAL(ik), ik=1,kjpindex ) /), kjpindex, kindex) |
---|
340 | CALL histwrite_p(hist_id, 'Areas', itau_sechiba+1, area, kjpindex, kindex) |
---|
341 | IF ( ok_stomate ) THEN |
---|
342 | CALL histwrite_p(hist_id_stom, 'Areas', itau_sechiba+1, area, kjpindex, kindex) |
---|
343 | CALL histwrite_p(hist_id_stom_IPCC, 'Areas', itau_sechiba+1, area, kjpindex, kindex) |
---|
344 | ENDIF |
---|
345 | |
---|
346 | CALL histwrite_p(hist_id, 'Contfrac', itau_sechiba+1, contfrac, kjpindex, kindex) |
---|
347 | IF ( is_omp_root .AND. hist_id > 0 ) THEN |
---|
348 | ! Always syncronize output after initialization |
---|
349 | CALL histsync(hist_id) |
---|
350 | END IF |
---|
351 | |
---|
352 | CALL histwrite_p(hist2_id, 'LandPoints', itau_sechiba+1, (/ ( REAL(ik), ik=1,kjpindex ) /), kjpindex, kindex) |
---|
353 | CALL histwrite_p(hist2_id, 'Areas', itau_sechiba+1, area, kjpindex, kindex) |
---|
354 | CALL histwrite_p(hist2_id, 'Contfrac', itau_sechiba+1, contfrac, kjpindex, kindex) |
---|
355 | IF ( is_omp_root .AND. hist2_id > 0 ) THEN |
---|
356 | ! Always syncronize output after initialization |
---|
357 | CALL histsync(hist2_id) |
---|
358 | ENDIF |
---|
359 | |
---|
360 | ! |
---|
361 | ! 3. call sechiba for continental points only |
---|
362 | ! |
---|
363 | IF ( printlev_loc >= 3 ) WRITE(numout,*) 'Calling sechiba_initialize' |
---|
364 | |
---|
365 | CALL sechiba_initialize( & |
---|
366 | itau_sechiba, iim*jjm, kjpindex, kindex, date0_shifted, & |
---|
367 | lalo, contfrac, neighbours, resolution, zzlev, & |
---|
368 | zu, zv, zqair, ztemp_air, ztemp_air, & |
---|
369 | zpetAcoef, zpeqAcoef, zpetBcoef, zpeqBcoef, & |
---|
370 | zprecip_rain, zprecip_snow, zlwdown, zswnet, zswdown, & |
---|
371 | zpb, rest_id, hist_id, hist2_id, & |
---|
372 | rest_id_stom, hist_id_stom, hist_id_stom_IPCC, & |
---|
373 | zcoastal, zriver, ztsol_rad, zvevapp, zqsurf, & |
---|
374 | zz0, zalbedo, zfluxsens, zfluxlat, zemis, & |
---|
375 | znetco2, zcarblu, ztemp_sol_new, zcdrag) |
---|
376 | |
---|
377 | IF ( printlev_loc >= 3 ) WRITE(numout,*) 'out of sechiba_initialize' |
---|
378 | ! |
---|
379 | ! 5. scatter output fields |
---|
380 | ! |
---|
381 | z0(:,:) = undef_sechiba |
---|
382 | coastalflow(:,:) = undef_sechiba |
---|
383 | riverflow(:,:) = undef_sechiba |
---|
384 | tsol_rad(:,:) = undef_sechiba |
---|
385 | vevapp(:,:) = undef_sechiba |
---|
386 | temp_sol_new(:,:) = undef_sechiba |
---|
387 | qsurf(:,:) = undef_sechiba |
---|
388 | albedo(:,:,:) = undef_sechiba |
---|
389 | fluxsens(:,:) = undef_sechiba |
---|
390 | fluxlat(:,:) = undef_sechiba |
---|
391 | emis(:,:) = undef_sechiba |
---|
392 | cdrag(:,:) = undef_sechiba |
---|
393 | |
---|
394 | DO ik=1, kjpindex |
---|
395 | j = ((kindex(ik)-1)/iim) + 1 |
---|
396 | i = (kindex(ik) - (j-1)*iim) |
---|
397 | |
---|
398 | z0(i,j) = zz0(ik) |
---|
399 | coastalflow(i,j) = zcoastal(ik) |
---|
400 | riverflow(i,j) = zriver(ik) |
---|
401 | tsol_rad(i,j) = ztsol_rad(ik) |
---|
402 | vevapp(i,j) = zvevapp(ik) |
---|
403 | temp_sol_new(i,j) = ztemp_sol_new(ik) |
---|
404 | qsurf(i,j) = zqsurf(ik) |
---|
405 | albedo(i,j,1) = zalbedo(ik,1) |
---|
406 | albedo(i,j,2) = zalbedo(ik,2) |
---|
407 | fluxsens(i,j) = zfluxsens(ik) |
---|
408 | fluxlat(i,j) = zfluxlat(ik) |
---|
409 | emis(i,j) = zemis(ik) |
---|
410 | cdrag(i,j) = zcdrag(ik) |
---|
411 | |
---|
412 | ENDDO |
---|
413 | |
---|
414 | ! |
---|
415 | ! 6. Transform the water fluxes into Kg/m^2s and m^3/s |
---|
416 | ! |
---|
417 | DO ik=1, kjpindex |
---|
418 | |
---|
419 | j = ((kindex(ik)-1)/iim) + 1 |
---|
420 | i = (kindex(ik) - (j-1)*iim) |
---|
421 | |
---|
422 | vevapp(i,j) = vevapp(i,j)/xrdt |
---|
423 | coastalflow(i,j) = coastalflow(i,j)/xrdt |
---|
424 | riverflow(i,j) = riverflow(i,j)/xrdt |
---|
425 | |
---|
426 | ENDDO |
---|
427 | |
---|
428 | IF (is_root_prc) CALL getin_dump |
---|
429 | |
---|
430 | l_first_intersurf = .FALSE. |
---|
431 | IF (printlev_loc >=3) WRITE (numout,*) ' intersurf_main done ' |
---|
432 | CALL ipslnlf_p(new_number=old_fileout) |
---|
433 | END SUBROUTINE intersurf_initialize_2d |
---|
434 | |
---|
435 | |
---|
436 | !! ============================================================================================================================= |
---|
437 | !! SUBROUTINE: intersurf_main_2d |
---|
438 | !! |
---|
439 | !>\BRIEF Main subroutine to call ORCHIDEE from dim2_driver using variables on a 2d grid. |
---|
440 | !! |
---|
441 | !! DESCRIPTION: This subroutine is the main interface for ORCHIDEE when it is called from the offline driver dim2_driver. |
---|
442 | !! The variables are all on the 2D grid including ocean points. intersurf_initialize_2d should be called before |
---|
443 | !! this subroutine is called. This subroutine is called at each time step. |
---|
444 | !! |
---|
445 | !! \n |
---|
446 | !_ ============================================================================================================================== |
---|
447 | |
---|
448 | SUBROUTINE intersurf_main_2d (kjit, iim, jjm, kjpindex, kindex, xrdt, & |
---|
449 | lrestart_read, lrestart_write, lon, lat, zcontfrac, zresolution, date0, & |
---|
450 | zlev, u, v, qair, temp_air, epot_air, ccanopy, & |
---|
451 | cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
452 | precip_rain, precip_snow, lwdown, swnet, swdown, pb, & |
---|
453 | vevapp, fluxsens, fluxlat, coastalflow, riverflow, & |
---|
454 | tsol_rad, temp_sol_new, qsurf, albedo, emis, z0, & |
---|
455 | coszang) |
---|
456 | ! coszang,soil_mc,litter_mc) |
---|
457 | IMPLICIT NONE |
---|
458 | |
---|
459 | !! 0. Variable and parameter declaration |
---|
460 | !! 0.1 Input variables |
---|
461 | INTEGER(i_std),INTENT (in) :: kjit !! Time step number |
---|
462 | INTEGER(i_std),INTENT (in) :: iim, jjm !! Dimension of input fields |
---|
463 | INTEGER(i_std),INTENT (in) :: kjpindex !! Number of continental points |
---|
464 | REAL(r_std),INTENT (in) :: xrdt !! Time step in seconds |
---|
465 | LOGICAL, INTENT (in) :: lrestart_read !! Logical for _restart_ file to read |
---|
466 | LOGICAL, INTENT (in) :: lrestart_write !! Logical for _restart_ file to write' |
---|
467 | REAL(r_std), INTENT (in) :: date0 !! Date at which kjit = 0 |
---|
468 | INTEGER(i_std),DIMENSION (kjpindex), INTENT (in) :: kindex !! Index for continental points |
---|
469 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: u !! Lowest level wind speed |
---|
470 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: v !! Lowest level wind speed |
---|
471 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: zlev !! Height of first layer |
---|
472 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: qair !! Lowest level specific humidity |
---|
473 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: precip_rain !! Rain precipitation |
---|
474 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: precip_snow !! Snow precipitation |
---|
475 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: lwdown !! Down-welling long-wave flux |
---|
476 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: swnet !! Net surface short-wave flux |
---|
477 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: swdown !! Downwelling surface short-wave flux |
---|
478 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: coszang !! Cosine of the solar zenith angle (unitless) |
---|
479 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: temp_air !! Air temperature in Kelvin |
---|
480 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: epot_air !! Air potential energy |
---|
481 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: ccanopy !! CO2 concentration in the canopy |
---|
482 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: petAcoef !! Coeficients A from the PBL resolution |
---|
483 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: peqAcoef !! One for T and another for q |
---|
484 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: petBcoef !! Coeficients B from the PBL resolution |
---|
485 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: peqBcoef !! One for T and another for q |
---|
486 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: pb !! Surface pressure |
---|
487 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: lon, lat !! Geographical coordinates |
---|
488 | REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: zcontfrac !! Fraction of continent in the grid |
---|
489 | REAL(r_std),DIMENSION (iim,jjm,2), INTENT(in) :: zresolution !! resolution in x and y dimensions |
---|
490 | |
---|
491 | !! 0.2 Output variables |
---|
492 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: z0 !! Surface roughness |
---|
493 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: coastalflow !! Diffuse flow of water into the ocean (m^3/dt) |
---|
494 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: riverflow !! Largest rivers flowing into the ocean (m^3/dt) |
---|
495 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: tsol_rad !! Radiative surface temperature |
---|
496 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: vevapp !! Total of evaporation |
---|
497 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: temp_sol_new !! New soil temperature |
---|
498 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: qsurf !! Surface specific humidity |
---|
499 | REAL(r_std),DIMENSION (iim,jjm,2), INTENT(out) :: albedo !! Albedo |
---|
500 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: fluxsens !! Sensible chaleur flux |
---|
501 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: fluxlat !! Latent chaleur flux |
---|
502 | REAL(r_std),DIMENSION (iim,jjm), INTENT(out) :: emis !! Emissivity |
---|
503 | ! REAL(r_std),DIMENSION (kjpindex,nbdl,nstm), INTENT(inout) :: soil_mc !! soil moisture content \f($m^3 \times m^3$)\f |
---|
504 | ! REAL(r_std),DIMENSION (kjpindex,nstm), INTENT(inout) :: litter_mc !! litter moisture content \f($m^3 \times m^3$)\f |
---|
505 | |
---|
506 | !! 0.3 Modified variables |
---|
507 | REAL(r_std),DIMENSION (iim,jjm), INTENT(inout) :: cdrag !! Cdrag |
---|
508 | |
---|
509 | !! 0.4 Local variables |
---|
510 | REAL(r_std),DIMENSION (kjpindex) :: zu !! Work array to keep u |
---|
511 | REAL(r_std),DIMENSION (kjpindex) :: zv !! Work array to keep v |
---|
512 | REAL(r_std),DIMENSION (kjpindex) :: zzlev !! Work array to keep zlev |
---|
513 | REAL(r_std),DIMENSION (kjpindex) :: zqair !! Work array to keep qair |
---|
514 | REAL(r_std),DIMENSION (kjpindex) :: zprecip_rain !! Work array to keep precip_rain |
---|
515 | REAL(r_std),DIMENSION (kjpindex) :: zprecip_snow !! Work array to keep precip_snow |
---|
516 | REAL(r_std),DIMENSION (kjpindex) :: zlwdown !! Work array to keep lwdown |
---|
517 | REAL(r_std),DIMENSION (kjpindex) :: zswnet !! Work array to keep swnet |
---|
518 | REAL(r_std),DIMENSION (kjpindex) :: zswdown !! Work array to keep swdown |
---|
519 | REAL(r_std),DIMENSION (kjpindex) :: zcoszang !! Work array to keep coszang |
---|
520 | REAL(r_std),DIMENSION (kjpindex) :: ztemp_air !! Work array to keep temp_air |
---|
521 | REAL(r_std),DIMENSION (kjpindex) :: zepot_air !! Work array to keep epot_air |
---|
522 | REAL(r_std),DIMENSION (kjpindex) :: zccanopy !! Work array to keep ccanopy |
---|
523 | REAL(r_std),DIMENSION (kjpindex) :: zpetAcoef !! Work array to keep petAcoef |
---|
524 | REAL(r_std),DIMENSION (kjpindex) :: zpeqAcoef !! Work array to keep peqAcoef |
---|
525 | REAL(r_std),DIMENSION (kjpindex) :: zpetBcoef !! Work array to keep petBcoef |
---|
526 | REAL(r_std),DIMENSION (kjpindex) :: zpeqBcoef !! Work array to keep peqVcoef |
---|
527 | REAL(r_std),DIMENSION (kjpindex) :: zcdrag !! Work array to keep cdrag |
---|
528 | REAL(r_std),DIMENSION (kjpindex) :: zpb !! Work array to keep pb |
---|
529 | REAL(r_std),DIMENSION (kjpindex) :: zz0 !! Work array to keep z0 |
---|
530 | REAL(r_std),DIMENSION (kjpindex) :: zcoastal !! Work array to keep coastalflow |
---|
531 | REAL(r_std),DIMENSION (kjpindex) :: zriver !! Work array to keep riverflow |
---|
532 | REAL(r_std),DIMENSION (kjpindex) :: znetco2 !! Work array to keep netco2flux |
---|
533 | REAL(r_std),DIMENSION (kjpindex) :: zcarblu !! Work array to keep fco2_land_use |
---|
534 | REAL(r_std),DIMENSION (kjpindex) :: ztsol_rad !! Work array to keep tsol_rad |
---|
535 | REAL(r_std),DIMENSION (kjpindex) :: zvevapp !! Work array to keep vevapp |
---|
536 | REAL(r_std),DIMENSION (kjpindex) :: ztemp_sol_new !! Work array to keep temp_sol_new |
---|
537 | REAL(r_std),DIMENSION (kjpindex) :: zqsurf !! Work array to keep qsurf |
---|
538 | REAL(r_std),DIMENSION (kjpindex,2) :: zalbedo !! Work array to keep albedo |
---|
539 | REAL(r_std),DIMENSION (kjpindex) :: zfluxsens !! Work array to keep fluxsens |
---|
540 | REAL(r_std),DIMENSION (kjpindex) :: zfluxlat !! Work array to keep fluxlat |
---|
541 | REAL(r_std),DIMENSION (kjpindex) :: zemis !! Work array to keep emis |
---|
542 | REAL(r_std),ALLOCATABLE, DIMENSION (:) :: soilth_lev !! Vertical soil axis for thermal scheme (m) |
---|
543 | INTEGER(i_std) :: i, j, ik |
---|
544 | INTEGER(i_std) :: ier |
---|
545 | INTEGER(i_std) :: itau_sechiba |
---|
546 | REAL(r_std) :: zlev_mean |
---|
547 | INTEGER :: old_fileout !! old Logical Int for std IO output |
---|
548 | |
---|
549 | CALL ipslnlf_p(new_number=numout,old_number=old_fileout) |
---|
550 | |
---|
551 | ! |
---|
552 | ! Shift the time step to phase the two models |
---|
553 | ! |
---|
554 | itau_sechiba = kjit + itau_offset |
---|
555 | ! |
---|
556 | |
---|
557 | ! Update the calendar in xios by sending the new time step |
---|
558 | CALL xios_orchidee_update_calendar(itau_sechiba) |
---|
559 | |
---|
560 | CALL intsurf_time( itau_sechiba, date0_shifted ) |
---|
561 | ! |
---|
562 | ! 1. gather input fields from kindex array |
---|
563 | ! Warning : I'm not sure this interface with one dimension array is the good one |
---|
564 | ! |
---|
565 | DO ik=1, kjpindex |
---|
566 | |
---|
567 | j = ((kindex(ik)-1)/iim) + 1 |
---|
568 | i = (kindex(ik) - (j-1)*iim) |
---|
569 | |
---|
570 | zu(ik) = u(i,j) |
---|
571 | zv(ik) = v(i,j) |
---|
572 | zzlev(ik) = zlev(i,j) |
---|
573 | zqair(ik) = qair(i,j) |
---|
574 | zprecip_rain(ik) = precip_rain(i,j)*xrdt |
---|
575 | zprecip_snow(ik) = precip_snow(i,j)*xrdt |
---|
576 | zlwdown(ik) = lwdown(i,j) |
---|
577 | zswnet(ik) = swnet(i,j) |
---|
578 | zswdown(ik) = swdown(i,j) |
---|
579 | zcoszang(ik) = coszang(i,j) |
---|
580 | ztemp_air(ik) = temp_air(i,j) |
---|
581 | zepot_air(ik) = epot_air(i,j) |
---|
582 | zccanopy(ik) = ccanopy(i,j) |
---|
583 | zpetAcoef(ik) = petAcoef(i,j) |
---|
584 | zpeqAcoef(ik) = peqAcoef(i,j) |
---|
585 | zpetBcoef(ik) = petBcoef(i,j) |
---|
586 | zpeqBcoef(ik) = peqBcoef(i,j) |
---|
587 | zcdrag(ik) = cdrag(i,j) |
---|
588 | zpb(ik) = pb(i,j) |
---|
589 | |
---|
590 | ENDDO |
---|
591 | ! |
---|
592 | IF (check_INPUTS) THEN |
---|
593 | WRITE(numout,*) "Intersurf_main_2D :" |
---|
594 | WRITE(numout,*) "Time step number = ",kjit |
---|
595 | WRITE(numout,*) "Dimension of input fields = ",iim, jjm |
---|
596 | WRITE(numout,*) "Number of continental points = ",kjpindex |
---|
597 | WRITE(numout,*) "Time step in seconds = ",xrdt |
---|
598 | WRITE(numout,*) "Logical for _restart_ file to read, write = ",lrestart_read,lrestart_write |
---|
599 | WRITE(numout,*) "Date at which kjit = 0 = ",date0 |
---|
600 | WRITE(numout,*) "Index for continental points = ",kindex |
---|
601 | WRITE(numout,*) "Lowest level wind speed North = ",zu |
---|
602 | WRITE(numout,*) "Lowest level wind speed East = ",zv |
---|
603 | WRITE(numout,*) "Height of first layer = ",zzlev |
---|
604 | WRITE(numout,*) "Lowest level specific humidity = ",zqair |
---|
605 | WRITE(numout,*) "Rain precipitation = ",zprecip_rain |
---|
606 | WRITE(numout,*) "Snow precipitation = ",zprecip_snow |
---|
607 | WRITE(numout,*) "Down-welling long-wave flux = ",zlwdown |
---|
608 | WRITE(numout,*) "Net surface short-wave flux = ",zswnet |
---|
609 | WRITE(numout,*) "Downwelling surface short-wave flux = ",zswdown |
---|
610 | WRITE(numout,*) "Air temperature in Kelvin = ",ztemp_air |
---|
611 | WRITE(numout,*) "Air potential energy = ",zepot_air |
---|
612 | WRITE(numout,*) "CO2 concentration in the canopy = ",zccanopy |
---|
613 | WRITE(numout,*) "Coeficients A from the PBL resolution = ",zpetAcoef |
---|
614 | WRITE(numout,*) "One for T and another for q = ",zpeqAcoef |
---|
615 | WRITE(numout,*) "Coeficients B from the PBL resolution = ",zpetBcoef |
---|
616 | WRITE(numout,*) "One for T and another for q = ",zpeqBcoef |
---|
617 | WRITE(numout,*) "Cdrag = ",zcdrag |
---|
618 | WRITE(numout,*) "Surface pressure = ",zpb |
---|
619 | WRITE(numout,*) "Geographical coordinates lon = ", (/ ( lon(ilandindex(ik), jlandindex(ik)), ik=1,kjpindex ) /) |
---|
620 | WRITE(numout,*) "Geographical coordinates lat = ", (/ ( lat(ilandindex(ik), jlandindex(ik)), ik=1,kjpindex ) /) |
---|
621 | WRITE(numout,*) "Fraction of continent in the grid = ",contfrac |
---|
622 | ENDIF |
---|
623 | |
---|
624 | ! |
---|
625 | ! 3. call sechiba for continental points only |
---|
626 | ! |
---|
627 | IF ( printlev_loc >= 3 ) WRITE(numout,*) 'Calling sechiba_main' |
---|
628 | |
---|
629 | CALL sechiba_main (itau_sechiba, iim*jjm, kjpindex, kindex, date0_shifted, & |
---|
630 | lrestart_read, lrestart_write, & |
---|
631 | lalo, contfrac, neighbours, resolution, & |
---|
632 | zzlev, zu, zv, zqair, zqair, ztemp_air, ztemp_air, zepot_air, zccanopy, & |
---|
633 | zcdrag, zpetAcoef, zpeqAcoef, zpetBcoef, zpeqBcoef, & |
---|
634 | zprecip_rain ,zprecip_snow, zlwdown, zswnet, zswdown, zcoszang, zpb, & |
---|
635 | zvevapp, zfluxsens, zfluxlat, zcoastal, zriver, znetco2, zcarblu, & |
---|
636 | ztsol_rad, ztemp_sol_new, zqsurf, zalbedo, zemis, zz0, & |
---|
637 | rest_id, hist_id, hist2_id, rest_id_stom, hist_id_stom, hist_id_stom_IPCC ) |
---|
638 | ! rest_id, hist_id, hist2_id, rest_id_stom, hist_id_stom, & |
---|
639 | ! hist_id_stom_IPCC,soil_mc,litter_mc ) |
---|
640 | IF ( printlev_loc >= 3 ) WRITE(numout,*) 'out of sechiba_main' |
---|
641 | |
---|
642 | ! |
---|
643 | ! 5. scatter output fields |
---|
644 | ! |
---|
645 | z0(:,:) = undef_sechiba |
---|
646 | coastalflow(:,:) = undef_sechiba |
---|
647 | riverflow(:,:) = undef_sechiba |
---|
648 | tsol_rad(:,:) = undef_sechiba |
---|
649 | vevapp(:,:) = undef_sechiba |
---|
650 | temp_sol_new(:,:) = undef_sechiba |
---|
651 | qsurf(:,:) = undef_sechiba |
---|
652 | albedo(:,:,:) = undef_sechiba |
---|
653 | fluxsens(:,:) = undef_sechiba |
---|
654 | fluxlat(:,:) = undef_sechiba |
---|
655 | emis(:,:) = undef_sechiba |
---|
656 | cdrag(:,:) = undef_sechiba |
---|
657 | ! |
---|
658 | DO ik=1, kjpindex |
---|
659 | |
---|
660 | |
---|
661 | j = ((kindex(ik)-1)/iim) + 1 |
---|
662 | i = (kindex(ik) - (j-1)*iim) |
---|
663 | |
---|
664 | z0(i,j) = zz0(ik) |
---|
665 | coastalflow(i,j) = zcoastal(ik) |
---|
666 | riverflow(i,j) = zriver(ik) |
---|
667 | tsol_rad(i,j) = ztsol_rad(ik) |
---|
668 | vevapp(i,j) = zvevapp(ik) |
---|
669 | temp_sol_new(i,j) = ztemp_sol_new(ik) |
---|
670 | qsurf(i,j) = zqsurf(ik) |
---|
671 | albedo(i,j,1) = zalbedo(ik,1) |
---|
672 | albedo(i,j,2) = zalbedo(ik,2) |
---|
673 | fluxsens(i,j) = zfluxsens(ik) |
---|
674 | fluxlat(i,j) = zfluxlat(ik) |
---|
675 | emis(i,j) = zemis(ik) |
---|
676 | cdrag(i,j) = zcdrag(ik) |
---|
677 | |
---|
678 | ENDDO |
---|
679 | |
---|
680 | CALL xios_orchidee_send_field("LandPoints" ,(/ ( REAL(ik), ik=1,kjpindex ) /)) |
---|
681 | CALL xios_orchidee_send_field("Areas", area) |
---|
682 | CALL xios_orchidee_send_field("Contfrac",contfrac) |
---|
683 | CALL xios_orchidee_send_field("evap",zvevapp*one_day/dt_sechiba) |
---|
684 | CALL xios_orchidee_send_field("evap_alma",zvevapp/dt_sechiba) |
---|
685 | CALL xios_orchidee_send_field("temp_sol_C",ztemp_sol_new-ZeroCelsius) |
---|
686 | CALL xios_orchidee_send_field("temp_sol_K",ztemp_sol_new) |
---|
687 | CALL xios_orchidee_send_field("fluxsens",zfluxsens) |
---|
688 | CALL xios_orchidee_send_field("fluxlat",zfluxlat) |
---|
689 | CALL xios_orchidee_send_field("alb_vis",zalbedo(:,1)) |
---|
690 | CALL xios_orchidee_send_field("alb_nir",zalbedo(:,2)) |
---|
691 | CALL xios_orchidee_send_field("tair",ztemp_air) |
---|
692 | CALL xios_orchidee_send_field("qair",zqair) |
---|
693 | CALL xios_orchidee_send_field("q2m",zqair) |
---|
694 | CALL xios_orchidee_send_field("t2m",ztemp_air) |
---|
695 | CALL xios_orchidee_send_field("swnet",zswnet) |
---|
696 | CALL xios_orchidee_send_field("swdown",zswdown) |
---|
697 | ! zpb in hPa, output in Pa |
---|
698 | CALL xios_orchidee_send_field("Psurf",zpb*100.) |
---|
699 | |
---|
700 | IF ( .NOT. almaoutput ) THEN |
---|
701 | ! |
---|
702 | ! scattered during the writing |
---|
703 | ! |
---|
704 | CALL histwrite_p (hist_id, 'evap', itau_sechiba, zvevapp, kjpindex, kindex) |
---|
705 | CALL histwrite_p (hist_id, 'coastalflow',itau_sechiba, zcoastal, kjpindex, kindex) |
---|
706 | CALL histwrite_p (hist_id, 'riverflow',itau_sechiba, zriver, kjpindex, kindex) |
---|
707 | CALL histwrite_p (hist_id, 'temp_sol', itau_sechiba, ztemp_sol_NEW, kjpindex, kindex) |
---|
708 | CALL histwrite_p (hist_id, 'tsol_max', itau_sechiba, ztemp_sol_NEW, kjpindex, kindex) |
---|
709 | CALL histwrite_p (hist_id, 'tsol_min', itau_sechiba, ztemp_sol_NEW, kjpindex, kindex) |
---|
710 | CALL histwrite_p (hist_id, 'fluxsens', itau_sechiba, zfluxsens, kjpindex, kindex) |
---|
711 | CALL histwrite_p (hist_id, 'fluxlat', itau_sechiba, zfluxlat, kjpindex, kindex) |
---|
712 | CALL histwrite_p (hist_id, 'swnet', itau_sechiba, zswnet, kjpindex, kindex) |
---|
713 | CALL histwrite_p (hist_id, 'swdown', itau_sechiba, zswdown, kjpindex, kindex) |
---|
714 | CALL histwrite_p (hist_id, 'alb_vis', itau_sechiba, zalbedo(:,1), kjpindex, kindex) |
---|
715 | CALL histwrite_p (hist_id, 'alb_nir', itau_sechiba, zalbedo(:,2), kjpindex, kindex) |
---|
716 | CALL histwrite_p (hist_id, 'tair', itau_sechiba, ztemp_air, kjpindex, kindex) |
---|
717 | CALL histwrite_p (hist_id, 'qair', itau_sechiba, zqair, kjpindex, kindex) |
---|
718 | CALL histwrite_p (hist_id, 'q2m', itau_sechiba, zqair, kjpindex, kindex) |
---|
719 | CALL histwrite_p (hist_id, 't2m', itau_sechiba, ztemp_air, kjpindex, kindex) |
---|
720 | CALL histwrite_p (hist2_id, 'evap', itau_sechiba, zvevapp, kjpindex, kindex) |
---|
721 | CALL histwrite_p (hist2_id, 'coastalflow',itau_sechiba, zcoastal, kjpindex, kindex) |
---|
722 | CALL histwrite_p (hist2_id, 'riverflow',itau_sechiba, zriver, kjpindex, kindex) |
---|
723 | CALL histwrite_p (hist2_id, 'temp_sol', itau_sechiba, ztemp_sol_NEW, kjpindex, kindex) |
---|
724 | CALL histwrite_p (hist2_id, 'tsol_max', itau_sechiba, ztemp_sol_NEW, kjpindex, kindex) |
---|
725 | CALL histwrite_p (hist2_id, 'tsol_min', itau_sechiba, ztemp_sol_NEW, kjpindex, kindex) |
---|
726 | CALL histwrite_p (hist2_id, 'fluxsens', itau_sechiba, zfluxsens, kjpindex, kindex) |
---|
727 | CALL histwrite_p (hist2_id, 'fluxlat', itau_sechiba, zfluxlat, kjpindex, kindex) |
---|
728 | CALL histwrite_p (hist2_id, 'swnet', itau_sechiba, zswnet, kjpindex, kindex) |
---|
729 | CALL histwrite_p (hist2_id, 'swdown', itau_sechiba, zswdown, kjpindex, kindex) |
---|
730 | CALL histwrite_p (hist2_id, 'alb_vis', itau_sechiba, zalbedo(:,1), kjpindex, kindex) |
---|
731 | CALL histwrite_p (hist2_id, 'alb_nir', itau_sechiba, zalbedo(:,2), kjpindex, kindex) |
---|
732 | CALL histwrite_p (hist2_id, 'tair', itau_sechiba, ztemp_air, kjpindex, kindex) |
---|
733 | CALL histwrite_p (hist2_id, 'qair', itau_sechiba, zqair, kjpindex, kindex) |
---|
734 | CALL histwrite_p (hist2_id, 'q2m', itau_sechiba, zqair, kjpindex, kindex) |
---|
735 | CALL histwrite_p (hist2_id, 't2m', itau_sechiba, ztemp_air, kjpindex, kindex) |
---|
736 | ELSE |
---|
737 | CALL histwrite_p (hist_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex) |
---|
738 | CALL histwrite_p (hist_id, 'SWnet', itau_sechiba, zswnet, kjpindex, kindex) |
---|
739 | CALL histwrite_p (hist_id, 'Qh', itau_sechiba, zfluxsens, kjpindex, kindex) |
---|
740 | CALL histwrite_p (hist_id, 'Qle', itau_sechiba, zfluxlat, kjpindex, kindex) |
---|
741 | CALL histwrite_p (hist_id, 'AvgSurfT', itau_sechiba, ztemp_sol_NEW, kjpindex, kindex) |
---|
742 | CALL histwrite_p (hist_id, 'RadT', itau_sechiba, ztemp_sol_NEW, kjpindex, kindex) |
---|
743 | CALL histwrite_p (hist_id, 'Tair', itau_sechiba, ztemp_air, kjpindex, kindex) |
---|
744 | CALL histwrite_p (hist_id, 'Qair', itau_sechiba, zqair, kjpindex, kindex) |
---|
745 | CALL histwrite_p (hist2_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex) |
---|
746 | CALL histwrite_p (hist2_id, 'SWnet', itau_sechiba, zswnet, kjpindex, kindex) |
---|
747 | CALL histwrite_p (hist2_id, 'Qh', itau_sechiba, zfluxsens, kjpindex, kindex) |
---|
748 | CALL histwrite_p (hist2_id, 'Qle', itau_sechiba, zfluxlat, kjpindex, kindex) |
---|
749 | CALL histwrite_p (hist2_id, 'AvgSurfT', itau_sechiba, ztemp_sol_NEW, kjpindex, kindex) |
---|
750 | CALL histwrite_p (hist2_id, 'RadT', itau_sechiba, ztemp_sol_NEW, kjpindex, kindex) |
---|
751 | ENDIF |
---|
752 | ! |
---|
753 | IF ( is_omp_root ) THEN |
---|
754 | IF ( (dw .EQ. xrdt) .AND. hist_id > 0 ) THEN |
---|
755 | ! Syncronize output but only if flag ok_histsync is set to true |
---|
756 | IF (ok_histsync) CALL histsync(hist_id) |
---|
757 | ENDIF |
---|
758 | END IF |
---|
759 | |
---|
760 | ! |
---|
761 | ! 6. Transform the water fluxes into Kg/m^2s and m^3/s |
---|
762 | ! |
---|
763 | DO ik=1, kjpindex |
---|
764 | |
---|
765 | j = ((kindex(ik)-1)/iim) + 1 |
---|
766 | i = (kindex(ik) - (j-1)*iim) |
---|
767 | |
---|
768 | vevapp(i,j) = vevapp(i,j)/xrdt |
---|
769 | coastalflow(i,j) = coastalflow(i,j)/xrdt |
---|
770 | riverflow(i,j) = riverflow(i,j)/xrdt |
---|
771 | |
---|
772 | ENDDO |
---|
773 | |
---|
774 | IF (printlev_loc >=3) WRITE (numout,*) ' intersurf_main done ' |
---|
775 | |
---|
776 | CALL ipslnlf_p(new_number=old_fileout) |
---|
777 | |
---|
778 | END SUBROUTINE intersurf_main_2d |
---|
779 | |
---|
780 | |
---|
781 | !! ============================================================================================================================= |
---|
782 | !! SUBROUTINE: init_intersurf |
---|
783 | !! |
---|
784 | !>\BRIEF Initialize grid information |
---|
785 | !! |
---|
786 | !! DESCRIPTION: This subroutine is called from LMDZ before first call to intersurf_main_gathered or |
---|
787 | !! intersurf_initialize_gathered |
---|
788 | !! |
---|
789 | !! \n |
---|
790 | !_ ============================================================================================================================== |
---|
791 | |
---|
792 | SUBROUTINE init_intersurf(nbp_l_lon,nbp_l_lat,kjpindex,kindex,orch_offset,orch_omp_size,orch_omp_rank,COMM) |
---|
793 | |
---|
794 | USE mod_orchidee_para |
---|
795 | USE timer |
---|
796 | IMPLICIT NONE |
---|
797 | |
---|
798 | INTEGER,INTENT(IN) :: nbp_l_lon |
---|
799 | INTEGER,INTENT(IN) :: nbp_l_lat |
---|
800 | INTEGER,INTENT(IN) :: kjpindex |
---|
801 | INTEGER,INTENT(IN) :: kindex(:) |
---|
802 | INTEGER,INTENT(IN) :: orch_offset |
---|
803 | INTEGER,INTENT(IN) :: COMM |
---|
804 | INTEGER,INTENT(IN) :: orch_omp_size |
---|
805 | INTEGER,INTENT(IN) :: orch_omp_rank |
---|
806 | |
---|
807 | INTEGER,DIMENSION(kjpindex) :: kindex_offset |
---|
808 | |
---|
809 | IF (orch_omp_rank==0) THEN |
---|
810 | CALL Init_timer |
---|
811 | CALL start_timer(timer_mpi) |
---|
812 | CALL set_grid_glo(nbp_l_lon,nbp_l_lat) |
---|
813 | ENDIF |
---|
814 | CALL barrier2_omp() |
---|
815 | CALL init_orchidee_data_para(kjpindex,kindex,orch_offset,orch_omp_size,orch_omp_rank,COMM) |
---|
816 | CALL Set_stdout_file('out_orchidee') |
---|
817 | |
---|
818 | IF (is_omp_root) CALL Allocate_grid_glo |
---|
819 | CALL barrier2_omp() |
---|
820 | CALL init_ioipsl_para |
---|
821 | |
---|
822 | kindex_offset(:)=kindex(:)+offset |
---|
823 | CALL gather(kindex_offset,index_g) |
---|
824 | CALL bcast(index_g) |
---|
825 | |
---|
826 | WRITE(numout,*) "kjpindex = ",kjpindex |
---|
827 | WRITE(numout,*) "offset for OMP = ",offset_omp |
---|
828 | WRITE(numout,*) "Index num local for continental points = ",kindex |
---|
829 | WRITE(numout,*) "Index num global for continental points = ",kindex_offset |
---|
830 | IF (is_omp_root) THEN |
---|
831 | WRITE(numout,*) "ROOT OMP, Index global MPI : ",kindex_mpi(:) |
---|
832 | ENDIF |
---|
833 | IF (is_root_prc) THEN |
---|
834 | WRITE(numout,*) "ROOT global, Index global : ",index_g(:) |
---|
835 | ENDIF |
---|
836 | |
---|
837 | END SUBROUTINE init_intersurf |
---|
838 | |
---|
839 | !! ============================================================================================================================= |
---|
840 | !! SUBROUTINE: intersurf_initialize_gathered |
---|
841 | !! |
---|
842 | !>\BRIEF Initialization and call to sechiba_initialize |
---|
843 | !! |
---|
844 | !! DESCRIPTION: Initialization of module variables, read options from parameter file, initialize output files and call to |
---|
845 | !! sechiba_initialize. |
---|
846 | !! |
---|
847 | !! This subroutine can be called directly from GCM(LMDZ). If it is not called before the first call to |
---|
848 | !! intersurf_main_gathered, then it will be done from there. This possibility is done to keep backward |
---|
849 | !! compatibility with LMDZ. |
---|
850 | !! |
---|
851 | !! \n |
---|
852 | !_ ============================================================================================================================== |
---|
853 | |
---|
854 | SUBROUTINE intersurf_initialize_gathered (kjit, iim_glo, jjm_glo, kjpindex, kindex, xrdt, & |
---|
855 | lrestart_read, lrestart_write, latlon, zcontfrac, zneighbours, zresolution, date0, & |
---|
856 | zlev, u, v, qair, temp_air, epot_air, & |
---|
857 | cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
858 | precip_rain, precip_snow, lwdown, swnet, swdown, pb, & |
---|
859 | vevapp, fluxsens, fluxlat, coastalflow, riverflow, & |
---|
860 | tsol_rad, temp_sol_new, qsurf, albedo, emis, z0, lon_scat_g, lat_scat_g, q2m, t2m, & |
---|
861 | field_out_names, fields_out, field_in_names, fields_in) |
---|
862 | |
---|
863 | USE mod_orchidee_para |
---|
864 | IMPLICIT NONE |
---|
865 | |
---|
866 | !! 0. Variable and parameter declaration |
---|
867 | !! 0.1 Input |
---|
868 | INTEGER(i_std),INTENT (in) :: kjit !! Time step number |
---|
869 | INTEGER(i_std),INTENT (in) :: iim_glo !! Dimension of global fields |
---|
870 | INTEGER(i_std),INTENT (in) :: jjm_glo !! Dimension of global fields |
---|
871 | INTEGER(i_std),INTENT (in) :: kjpindex !! Number of continental points |
---|
872 | REAL(r_std),INTENT (in) :: xrdt !! Time step in seconds |
---|
873 | LOGICAL, INTENT (in) :: lrestart_read !! Logical for _restart_ file to read |
---|
874 | LOGICAL, INTENT (in) :: lrestart_write !! Logical for _restart_ file to write' |
---|
875 | REAL(r_std), INTENT (in) :: date0 !! Date at which kjit = 0 |
---|
876 | INTEGER(i_std),DIMENSION (kjpindex), INTENT (in) :: kindex !! Index for continental points |
---|
877 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: u !! Lowest level wind speed |
---|
878 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: v !! Lowest level wind speed |
---|
879 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: zlev !! Height of first layer |
---|
880 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: qair !! Lowest level specific humidity |
---|
881 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: precip_rain !! Rain precipitation |
---|
882 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: precip_snow !! Snow precipitation |
---|
883 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: lwdown !! Down-welling long-wave flux |
---|
884 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: swnet !! Net surface short-wave flux |
---|
885 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: swdown !! Downwelling surface short-wave flux |
---|
886 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: temp_air !! Air temperature in Kelvin |
---|
887 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: epot_air !! Air potential energy |
---|
888 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: petAcoef !! Coeficients A from the PBL resolution |
---|
889 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: peqAcoef !! One for T and another for q |
---|
890 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: petBcoef !! Coeficients B from the PBL resolution |
---|
891 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: peqBcoef !! One for T and another for q |
---|
892 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: pb !! Surface pressure |
---|
893 | REAL(r_std),DIMENSION (kjpindex,2), INTENT(in) :: latlon !! Geographical coordinates |
---|
894 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: zcontfrac !! Fraction of continent |
---|
895 | INTEGER(i_std),DIMENSION (kjpindex,8), INTENT(in) :: zneighbours !! neighbours |
---|
896 | REAL(r_std),DIMENSION (kjpindex,2), INTENT(in) :: zresolution !! size of the grid box |
---|
897 | REAL(r_std),DIMENSION (iim_glo,jjm_glo), INTENT(IN) :: lon_scat_g !! The scattered values for longitude |
---|
898 | REAL(r_std),DIMENSION (iim_glo,jjm_glo), INTENT(IN) :: lat_scat_g !! The scattered values for latitudes |
---|
899 | |
---|
900 | !! 0.2 Output variables |
---|
901 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: z0 !! Surface roughness |
---|
902 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: coastalflow !! Diffuse flow of water into the ocean (m^3/dt) |
---|
903 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: riverflow !! Largest rivers flowing into the ocean (m^3/dt) |
---|
904 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: tsol_rad !! Radiative surface temperature |
---|
905 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: vevapp !! Total of evaporation |
---|
906 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: temp_sol_new !! New soil temperature |
---|
907 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: qsurf !! Surface specific humidity |
---|
908 | REAL(r_std),DIMENSION (kjpindex,2), INTENT(out) :: albedo !! Albedo |
---|
909 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: fluxsens !! Sensible chaleur flux |
---|
910 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: fluxlat !! Latent chaleur flux |
---|
911 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: emis !! Emissivity |
---|
912 | |
---|
913 | !! 0.3 Modified variables |
---|
914 | REAL(r_std),DIMENSION (kjpindex), INTENT(inout) :: cdrag !! Cdrag |
---|
915 | |
---|
916 | !! 0.4 Optional input and output variables |
---|
917 | REAL(r_std),DIMENSION (kjpindex), INTENT(in), OPTIONAL :: q2m !! Surface specific humidity |
---|
918 | REAL(r_std),DIMENSION (kjpindex), INTENT(in), OPTIONAL :: t2m !! Surface air temperature |
---|
919 | CHARACTER(LEN=*),DIMENSION(:), OPTIONAL, INTENT(IN) :: field_in_names !! Names for deposit variables to be transported |
---|
920 | !! from chemistry model by GCM to ORCHIDEE |
---|
921 | REAL(r_std),DIMENSION(:,:), OPTIONAL, INTENT(IN) :: fields_in !! Fields for deposit variables to be transported |
---|
922 | !! from chemistry model by GCM to ORCHIDEE |
---|
923 | CHARACTER(LEN=*),DIMENSION(:), OPTIONAL, INTENT(IN) :: field_out_names!! Names for emission variables to be transported |
---|
924 | !! to chemistry model by GCM from ORCHIDEE |
---|
925 | REAL(r_std),DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: fields_out !! Fields for emission variables to be transported |
---|
926 | !! to chemistry model by GCM from ORCHIDEE |
---|
927 | |
---|
928 | |
---|
929 | !! 0.5 Local variables |
---|
930 | REAL(r_std),DIMENSION (kjpindex) :: zprecip_rain !! Work array to keep precip_rain |
---|
931 | REAL(r_std),DIMENSION (kjpindex) :: zprecip_snow !! Work array to keep precip_snow |
---|
932 | REAL(r_std),DIMENSION (kjpindex) :: zz0 !! Work array to keep z0 |
---|
933 | REAL(r_std),DIMENSION (kjpindex) :: zcdrag !! Work array for surface drag |
---|
934 | REAL(r_std),DIMENSION (kjpindex) :: zcoastal !! Work array to keep coastal flow |
---|
935 | REAL(r_std),DIMENSION (kjpindex) :: zriver !! Work array to keep river out flow |
---|
936 | REAL(r_std),DIMENSION (kjpindex) :: znetco2 !! Work array to keep netco2flux |
---|
937 | REAL(r_std),DIMENSION (kjpindex) :: zcarblu !! Work array to keep fco2_land_use |
---|
938 | REAL(r_std),DIMENSION (kjpindex) :: ztsol_rad !! Work array to keep tsol_rad |
---|
939 | REAL(r_std),DIMENSION (kjpindex) :: zvevapp !! Work array to keep vevapp |
---|
940 | REAL(r_std),DIMENSION (kjpindex) :: ztemp_sol_new !! Work array to keep temp_sol_new |
---|
941 | REAL(r_std),DIMENSION (kjpindex) :: zqsurf !! Work array to keep qsurf |
---|
942 | REAL(r_std),DIMENSION (kjpindex,2) :: zalbedo !! Work array to keep albedo |
---|
943 | REAL(r_std),DIMENSION (kjpindex) :: zfluxsens !! Work array to keep fluxsens |
---|
944 | REAL(r_std),DIMENSION (kjpindex) :: zfluxlat !! Work array to keep fluxlat |
---|
945 | REAL(r_std),DIMENSION (kjpindex) :: zemis !! Work array to keep emis |
---|
946 | REAL(r_std),ALLOCATABLE, DIMENSION (:) :: soilth_lev !! Vertical soil axis for thermal scheme (m) |
---|
947 | REAL(r_std),DIMENSION (kjpindex) :: q2m_loc !! Work array for q2m or qair |
---|
948 | REAL(r_std),DIMENSION (kjpindex) :: t2m_loc !! Work array for t2m or temp_air |
---|
949 | REAL(r_std),DIMENSION (:,:),ALLOCATABLE :: lon_scat !! The scattered values for longitude |
---|
950 | REAL(r_std),DIMENSION (:,:),ALLOCATABLE :: lat_scat !! The scattered values for latitude |
---|
951 | INTEGER(i_std) :: i, j, ik |
---|
952 | INTEGER(i_std) :: ier |
---|
953 | INTEGER(i_std) :: itau_sechiba |
---|
954 | REAL(r_std) :: mx, zlev_mean |
---|
955 | REAL(r_std), ALLOCATABLE, DIMENSION(:,:) :: tmp_lon, tmp_lat, tmp_lev |
---|
956 | INTEGER :: old_fileout !! old Logical Int for std IO output |
---|
957 | REAL,ALLOCATABLE,DIMENSION(:,:) :: lalo_mpi |
---|
958 | REAL,ALLOCATABLE,DIMENSION(:) :: zlev_glo1D |
---|
959 | REAL(r_std),DIMENSION (kjpindex) :: landpoints !! Land point vector |
---|
960 | |
---|
961 | |
---|
962 | |
---|
963 | CALL ipslnlf_p(new_number=numout, old_number=old_fileout) |
---|
964 | ! |
---|
965 | ! Configuration of SSL specific parameters |
---|
966 | ! |
---|
967 | CALL control_initialize(xrdt) |
---|
968 | |
---|
969 | ! Initialize specific write level |
---|
970 | printlev_loc=get_printlev('instersurf') |
---|
971 | |
---|
972 | IF ( printlev_loc>=1 ) WRITE(numout,*) 'Entering intersurf_initialize_gathered' |
---|
973 | |
---|
974 | ! Set the variable ok_q2m_t2m=true if q2m and t2m are present in the call from the gcm. |
---|
975 | ! If one of the variables are not present in this subroutine, set ok_q2m_t2m=.FALSE. |
---|
976 | ! Otherwise do not change the current value. Note that the current value for ok_q2m_t2m comes |
---|
977 | ! either from default initialization (true) or from intersurf_main_gathered. |
---|
978 | IF (.NOT. PRESENT(q2m) .OR. .NOT. PRESENT(t2m)) THEN |
---|
979 | ok_q2m_t2m=.FALSE. |
---|
980 | END IF |
---|
981 | |
---|
982 | IF (ok_q2m_t2m) THEN |
---|
983 | t2m_loc=t2m |
---|
984 | q2m_loc=q2m |
---|
985 | ELSE |
---|
986 | t2m_loc=temp_air |
---|
987 | q2m_loc=qair |
---|
988 | END IF |
---|
989 | |
---|
990 | CALL intsurf_time( kjit, date0 ) |
---|
991 | |
---|
992 | |
---|
993 | CALL ioget_calendar (one_year, one_day) |
---|
994 | |
---|
995 | IF (is_omp_root) THEN |
---|
996 | ALLOCATE(lon_scat(iim_g,jj_nb)) |
---|
997 | ALLOCATE(lat_scat(iim_g,jj_nb)) |
---|
998 | ELSE |
---|
999 | ALLOCATE(lon_scat(1,1)) |
---|
1000 | ALLOCATE(lat_scat(1,1)) |
---|
1001 | ENDIF |
---|
1002 | |
---|
1003 | CALL init_WriteField_p |
---|
1004 | ! |
---|
1005 | ! Allocation of grid variables |
---|
1006 | ! |
---|
1007 | CALL init_grid ( kjpindex ) |
---|
1008 | ! |
---|
1009 | ! Create the internal coordinate table |
---|
1010 | ! |
---|
1011 | lalo(:,:) = latlon(:,:) |
---|
1012 | CALL gather(lalo,lalo_g) |
---|
1013 | ! |
---|
1014 | !- |
---|
1015 | !- Store variable to help describe the grid |
---|
1016 | !- once the points are gathered. |
---|
1017 | !- |
---|
1018 | neighbours(:,:) = zneighbours(:,:) |
---|
1019 | CALL gather(neighbours,neighbours_g) |
---|
1020 | ! |
---|
1021 | resolution(:,:) = zresolution(:,:) |
---|
1022 | CALL gather(resolution,resolution_g) |
---|
1023 | ! |
---|
1024 | area(:) = resolution(:,1)*resolution(:,2) |
---|
1025 | CALL gather(area,area_g) |
---|
1026 | ! |
---|
1027 | !- Store the fraction of the continents only once so that the user |
---|
1028 | !- does not change them afterwards. |
---|
1029 | ! |
---|
1030 | contfrac(:) = zcontfrac(:) |
---|
1031 | CALL gather(contfrac,contfrac_g) |
---|
1032 | ! |
---|
1033 | ! |
---|
1034 | ! Create the internal coordinate table |
---|
1035 | ! |
---|
1036 | IF ( (.NOT.ALLOCATED(tmp_lon))) THEN |
---|
1037 | ALLOCATE(tmp_lon(iim_g,jj_nb)) |
---|
1038 | ENDIF |
---|
1039 | IF ( (.NOT.ALLOCATED(tmp_lat))) THEN |
---|
1040 | ALLOCATE(tmp_lat(iim_g,jj_nb)) |
---|
1041 | ENDIF |
---|
1042 | IF ( (.NOT.ALLOCATED(tmp_lev))) THEN |
---|
1043 | ALLOCATE(tmp_lev(iim_g,jj_nb)) |
---|
1044 | ENDIF |
---|
1045 | ! |
---|
1046 | ! Either we have the scattered coordinates as arguments or |
---|
1047 | ! we have to do the work here. |
---|
1048 | ! |
---|
1049 | IF (is_omp_root) THEN |
---|
1050 | lon_scat(:,:)=zero |
---|
1051 | lat_scat(:,:)=zero |
---|
1052 | CALL scatter2D_mpi(lon_scat_g,lon_scat) |
---|
1053 | CALL scatter2D_mpi(lat_scat_g,lat_scat) |
---|
1054 | lon_scat(:,1)=lon_scat(:,2) |
---|
1055 | lon_scat(:,jj_nb)=lon_scat(:,2) |
---|
1056 | lat_scat(:,1)=lat_scat(iim_g,1) |
---|
1057 | lat_scat(:,jj_nb)=lat_scat(1,jj_nb) |
---|
1058 | |
---|
1059 | tmp_lon(:,:) = lon_scat(:,:) |
---|
1060 | tmp_lat(:,:) = lat_scat(:,:) |
---|
1061 | |
---|
1062 | IF (is_mpi_root) THEN |
---|
1063 | lon_g(:,:) = lon_scat_g(:,:) |
---|
1064 | lat_g(:,:) = lat_scat_g(:,:) |
---|
1065 | ENDIF |
---|
1066 | ENDIF |
---|
1067 | ! |
---|
1068 | |
---|
1069 | !ANNE ici possibilite de calculer la grille du modele ? (lignes 965 ?? |
---|
1070 | |
---|
1071 | |
---|
1072 | !ANNE calcul zlev, conserve la version de Martial |
---|
1073 | IF (is_root_prc) ALLOCATE(zlev_glo1D(nbp_glo)) |
---|
1074 | CALL gather(zlev,zlev_glo1D) |
---|
1075 | |
---|
1076 | IF (is_root_prc) THEN |
---|
1077 | DO ik=1, nbp_glo |
---|
1078 | j = INT( (index_g(ik)-1) / iim_g ) + 1 |
---|
1079 | i = index_g(ik) - (j-1) * iim_g |
---|
1080 | zlev_g(i,j) = zlev_glo1D(ik) |
---|
1081 | ENDDO |
---|
1082 | ENDIF |
---|
1083 | |
---|
1084 | !Config Key = FORCE_CO2_VEG |
---|
1085 | !Config Desc = Flag to force the value of atmospheric CO2 for vegetation. |
---|
1086 | !Config If = Only in coupled mode |
---|
1087 | !Config Def = FALSE |
---|
1088 | !Config Help = If this flag is set to true, the ATM_CO2 parameter is used |
---|
1089 | !Config to prescribe the atmospheric CO2. |
---|
1090 | !Config This Flag is only use in couple mode. |
---|
1091 | !Config Units = [FLAG] |
---|
1092 | fatmco2=.FALSE. |
---|
1093 | CALL getin_p('FORCE_CO2_VEG',fatmco2) |
---|
1094 | ! |
---|
1095 | ! Next flag is only use in couple mode with a gcm in intersurf. |
---|
1096 | ! In forced mode, it has already been read and set in driver. |
---|
1097 | IF ( fatmco2 ) THEN |
---|
1098 | !Config Key = ATM_CO2 |
---|
1099 | !Config IF = FORCE_CO2_VEG (only in coupled mode) |
---|
1100 | !Config Desc = Value for atm CO2 |
---|
1101 | !Config Def = 350. |
---|
1102 | !Config Help = Value to prescribe the atm CO2. |
---|
1103 | !Config For pre-industrial simulations, the value is 286.2 . |
---|
1104 | !Config 348. for 1990 year. |
---|
1105 | !Config Units = [ppm] |
---|
1106 | atmco2=350. |
---|
1107 | CALL getin_p('ATM_CO2',atmco2) |
---|
1108 | WRITE(numout,*) 'atmco2 ',atmco2 |
---|
1109 | ENDIF |
---|
1110 | |
---|
1111 | CALL ioipslctrl_restini(kjit, date0, xrdt, rest_id, rest_id_stom, itau_offset, date0_shifted) |
---|
1112 | itau_sechiba = kjit + itau_offset |
---|
1113 | |
---|
1114 | !!- Initialize module for output with XIOS |
---|
1115 | ! |
---|
1116 | ! Get the vertical soil levels for the thermal scheme, to be used in xios_orchidee_init |
---|
1117 | ALLOCATE(soilth_lev(ngrnd), stat=ier) |
---|
1118 | IF (ier /= 0) THEN |
---|
1119 | CALL ipslerr_p(3,'intersurf_main_gathered', 'Error in allocation of soilth_lev','','') |
---|
1120 | END IF |
---|
1121 | IF (hydrol_cwrr) THEN |
---|
1122 | soilth_lev(1:ngrnd) = znt(:) |
---|
1123 | ELSE |
---|
1124 | soilth_lev(1:ngrnd) = thermosoilc_levels() |
---|
1125 | END IF |
---|
1126 | |
---|
1127 | CALL xios_orchidee_init( MPI_COMM_ORCH, & |
---|
1128 | date0, year, month, day, & |
---|
1129 | tmp_lon, tmp_lat, soilth_lev ) |
---|
1130 | |
---|
1131 | !- Initialize IOIPSL sechiba output files |
---|
1132 | CALL ioipslctrl_history(iim_g, jj_nb, tmp_lon, tmp_lat, kindex, kjpindex, itau_sechiba, & |
---|
1133 | date0_shifted, xrdt, hist_id, hist2_id, hist_id_stom, hist_id_stom_IPCC) |
---|
1134 | |
---|
1135 | CALL bcast_omp(hist_id) |
---|
1136 | CALL bcast_omp(hist2_id) |
---|
1137 | CALL bcast_omp(hist_id_stom) |
---|
1138 | CALL bcast_omp(hist_id_stom_IPCC) |
---|
1139 | |
---|
1140 | ! Count number of extra output fields to the GCM if it is not already done. |
---|
1141 | IF (nb_fields_out == -1) THEN |
---|
1142 | ! nb_fields_out is not yet calculated. Do it now. |
---|
1143 | ! This means that the call is done directly from GCM. |
---|
1144 | IF (PRESENT(field_out_names)) THEN |
---|
1145 | nb_fields_out=SIZE(field_out_names) |
---|
1146 | ELSE |
---|
1147 | nb_fields_out=0 |
---|
1148 | ENDIF |
---|
1149 | END IF |
---|
1150 | |
---|
1151 | ! Count number of extra input fields to the GCM if it is not already done. |
---|
1152 | IF (nb_fields_in == -1) THEN |
---|
1153 | ! nb_fields_in is not yet calculated. Do it now. |
---|
1154 | ! This means that the call is done directly from GCM. |
---|
1155 | IF (PRESENT(field_in_names)) THEN |
---|
1156 | nb_fields_in=SIZE(field_in_names) |
---|
1157 | ELSE |
---|
1158 | nb_fields_in=0 |
---|
1159 | ENDIF |
---|
1160 | END IF |
---|
1161 | |
---|
1162 | |
---|
1163 | ! |
---|
1164 | !! Change to be in the orchidee context for XIOS |
---|
1165 | ! |
---|
1166 | CALL xios_orchidee_change_context("orchidee") |
---|
1167 | |
---|
1168 | ! |
---|
1169 | ! Shift the time step to phase the two models |
---|
1170 | ! |
---|
1171 | itau_sechiba = kjit + itau_offset |
---|
1172 | |
---|
1173 | ! Update the calendar in xios by sending the new time step |
---|
1174 | ! Special case : the model is only in initialization phase and the current itau_sechiba is not a real time step. |
---|
1175 | ! Therefor give itau_sechiba+1 to xios to have a correct time axis in output files. |
---|
1176 | CALL xios_orchidee_update_calendar(itau_sechiba+1) |
---|
1177 | |
---|
1178 | CALL intsurf_time( itau_sechiba, date0_shifted ) |
---|
1179 | |
---|
1180 | ! |
---|
1181 | ! 1. Just change the units of some input fields |
---|
1182 | ! |
---|
1183 | DO ik=1, kjpindex |
---|
1184 | |
---|
1185 | zprecip_rain(ik) = precip_rain(ik)*xrdt |
---|
1186 | zprecip_snow(ik) = precip_snow(ik)*xrdt |
---|
1187 | zcdrag(ik) = cdrag(ik) |
---|
1188 | |
---|
1189 | ENDDO |
---|
1190 | |
---|
1191 | ! Fields for deposit variables : to be transport from chemistry model by GCM to ORCHIDEE. |
---|
1192 | ! There are currently no fields to be transported into ORCHIDEE in this way |
---|
1193 | DO i = 1, nb_fields_in |
---|
1194 | WRITE(numout,*) i," Champ = ",TRIM(field_in_names(i)) |
---|
1195 | SELECT CASE(TRIM(field_in_names(i))) |
---|
1196 | CASE DEFAULT |
---|
1197 | CALL ipslerr_p (3,'intsurf_gathered', & |
---|
1198 | 'You ask in GCM an unknown field '//TRIM(field_in_names(i))//& |
---|
1199 | ' to give to ORCHIDEE for this specific version.',& |
---|
1200 | 'This model won''t be able to continue.', & |
---|
1201 | '(check your tracer parameters in GCM)') |
---|
1202 | END SELECT |
---|
1203 | ENDDO |
---|
1204 | |
---|
1205 | ! |
---|
1206 | ! 3. save the grid |
---|
1207 | ! |
---|
1208 | landpoints(:)=(/ ( REAL(ik), ik=1,kjpindex ) /) |
---|
1209 | CALL histwrite_p(hist_id, 'LandPoints', itau_sechiba+1, landpoints, kjpindex, kindex) |
---|
1210 | CALL histwrite_p(hist_id, 'Areas', itau_sechiba+1, area, kjpindex, kindex) |
---|
1211 | IF ( ok_stomate ) THEN |
---|
1212 | CALL histwrite_p(hist_id_stom, 'Areas', itau_sechiba+1, area, kjpindex, kindex) |
---|
1213 | IF ( hist_id_stom_ipcc > 0 ) & |
---|
1214 | CALL histwrite_p(hist_id_stom_IPCC, 'Areas', itau_sechiba+1, area, kjpindex, kindex) |
---|
1215 | ENDIF |
---|
1216 | CALL histwrite_p(hist_id, 'Contfrac', itau_sechiba+1, contfrac, kjpindex, kindex) |
---|
1217 | |
---|
1218 | ! Syncronize output but only if flag ok_histsync is set to true |
---|
1219 | IF (ok_histsync) THEN |
---|
1220 | IF (is_omp_root .AND. hist_id > 0) THEN |
---|
1221 | CALL histsync(hist_id) |
---|
1222 | END IF |
---|
1223 | END IF |
---|
1224 | |
---|
1225 | IF ( hist2_id > 0 ) THEN |
---|
1226 | CALL histwrite_p(hist2_id, 'LandPoints', itau_sechiba+1, landpoints, kjpindex, kindex) |
---|
1227 | CALL histwrite_p(hist2_id, 'Areas', itau_sechiba+1, area, kjpindex, kindex) |
---|
1228 | CALL histwrite_p(hist2_id, 'Contfrac', itau_sechiba+1, contfrac, kjpindex, kindex) |
---|
1229 | |
---|
1230 | ! Syncronize output but only if flag ok_histsync is set to true |
---|
1231 | IF (ok_histsync .AND. is_omp_root) THEN |
---|
1232 | CALL histsync(hist2_id) |
---|
1233 | ENDIF |
---|
1234 | ENDIF |
---|
1235 | ! |
---|
1236 | |
---|
1237 | ! |
---|
1238 | ! 4. call sechiba for continental points only |
---|
1239 | ! |
---|
1240 | IF ( printlev_loc>=3 ) WRITE(numout,*) 'Calling sechiba_initialize' |
---|
1241 | |
---|
1242 | CALL sechiba_initialize( & |
---|
1243 | itau_sechiba, iim_g*jj_nb, kjpindex, kindex, date0_shifted, & |
---|
1244 | lalo, contfrac, neighbours, resolution, zlev, & |
---|
1245 | u, v, qair, t2m_loc, temp_air, & |
---|
1246 | petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
1247 | zprecip_rain, zprecip_snow, lwdown, swnet, swdown, & |
---|
1248 | pb, rest_id, hist_id, hist2_id, & |
---|
1249 | rest_id_stom, hist_id_stom, hist_id_stom_IPCC, & |
---|
1250 | zcoastal, zriver, ztsol_rad, zvevapp, zqsurf, & |
---|
1251 | zz0, zalbedo, zfluxsens, zfluxlat, zemis, & |
---|
1252 | znetco2, zcarblu, ztemp_sol_new, zcdrag) |
---|
1253 | |
---|
1254 | IF ( printlev_loc>=3 ) WRITE(numout,*) 'Out of sechiba_initialize' |
---|
1255 | |
---|
1256 | ! |
---|
1257 | ! 6. scatter output fields |
---|
1258 | ! |
---|
1259 | z0(:) = undef_sechiba |
---|
1260 | coastalflow(:) = undef_sechiba |
---|
1261 | riverflow(:) = undef_sechiba |
---|
1262 | tsol_rad(:) = undef_sechiba |
---|
1263 | vevapp(:) = undef_sechiba |
---|
1264 | temp_sol_new(:) = undef_sechiba |
---|
1265 | qsurf(:) = undef_sechiba |
---|
1266 | albedo(:,1) = undef_sechiba |
---|
1267 | albedo(:,2) = undef_sechiba |
---|
1268 | fluxsens(:) = undef_sechiba |
---|
1269 | fluxlat(:) = undef_sechiba |
---|
1270 | emis(:) = undef_sechiba |
---|
1271 | cdrag(:) = undef_sechiba |
---|
1272 | |
---|
1273 | DO ik=1, kjpindex |
---|
1274 | z0(ik) = zz0(ik) |
---|
1275 | coastalflow(ik) = zcoastal(ik) |
---|
1276 | riverflow(ik) = zriver(ik) |
---|
1277 | tsol_rad(ik) = ztsol_rad(ik) |
---|
1278 | vevapp(ik) = zvevapp(ik) |
---|
1279 | temp_sol_new(ik) = ztemp_sol_new(ik) |
---|
1280 | qsurf(ik) = zqsurf(ik) |
---|
1281 | albedo(ik,1) = zalbedo(ik,1) |
---|
1282 | albedo(ik,2) = zalbedo(ik,2) |
---|
1283 | fluxsens(ik) = zfluxsens(ik) |
---|
1284 | fluxlat(ik) = zfluxlat(ik) |
---|
1285 | emis(ik) = zemis(ik) |
---|
1286 | cdrag(ik) = zcdrag(ik) |
---|
1287 | ENDDO |
---|
1288 | |
---|
1289 | ! |
---|
1290 | ! 7. Transform the water fluxes into Kg/m^2s and m^3/s |
---|
1291 | ! |
---|
1292 | DO ik=1, kjpindex |
---|
1293 | vevapp(ik) = vevapp(ik)/xrdt |
---|
1294 | coastalflow(ik) = coastalflow(ik)/xrdt |
---|
1295 | riverflow(ik) = riverflow(ik)/xrdt |
---|
1296 | ENDDO |
---|
1297 | |
---|
1298 | ! Fields for emission variables : to be transport by GCM to chemistry model. |
---|
1299 | DO i = 1, nb_fields_out |
---|
1300 | SELECT CASE(TRIM(field_out_names(i))) |
---|
1301 | CASE("fCO2_land") |
---|
1302 | fields_out(:,i)=znetco2(:) |
---|
1303 | CASE("fCO2_land_use") |
---|
1304 | fields_out(:,i)=zcarblu(:) |
---|
1305 | CASE DEFAULT |
---|
1306 | CALL ipslerr_p (3,'intsurf_gathered', & |
---|
1307 | 'You ask from GCM an unknown field '//TRIM(field_out_names(i))//& |
---|
1308 | ' to ORCHIDEE for this specific version.',& |
---|
1309 | 'This model won''t be able to continue.', & |
---|
1310 | '(check your tracer parameters in GCM)') |
---|
1311 | END SELECT |
---|
1312 | END DO |
---|
1313 | |
---|
1314 | IF(is_root_prc) CALL getin_dump |
---|
1315 | l_first_intersurf = .FALSE. |
---|
1316 | |
---|
1317 | CALL ipslnlf_p(new_number=old_fileout) |
---|
1318 | ! |
---|
1319 | !! Change back to be in the LMDZ context for XIOS |
---|
1320 | ! |
---|
1321 | CALL xios_orchidee_change_context("LMDZ") |
---|
1322 | |
---|
1323 | END SUBROUTINE intersurf_initialize_gathered |
---|
1324 | |
---|
1325 | |
---|
1326 | !! ============================================================================================================================= |
---|
1327 | !! SUBROUTINE: intersurf_main_gathered |
---|
1328 | !! |
---|
1329 | !>\BRIEF Main subroutine to call ORCHIDEE from the gcm (LMDZ) using variables on a 1D grid with only land points. |
---|
1330 | !! |
---|
1331 | !! DESCRIPTION: This subroutine is the main interface for ORCHIDEE when it is called from the gcm (LMDZ). |
---|
1332 | !! The variables are all gathered before entering this subroutine on the 1D grid with only landpoints. |
---|
1333 | !! |
---|
1334 | !! \n |
---|
1335 | !_ ============================================================================================================================== |
---|
1336 | |
---|
1337 | SUBROUTINE intersurf_main_gathered (kjit, iim_glo, jjm_glo, kjpindex, kindex, xrdt, & |
---|
1338 | lrestart_read, lrestart_write, latlon, zcontfrac, zneighbours, zresolution, date0, & |
---|
1339 | zlev, u, v, qair, temp_air, epot_air, ccanopy, & |
---|
1340 | cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
1341 | precip_rain, precip_snow, lwdown, swnet, swdown, pb, & |
---|
1342 | vevapp, fluxsens, fluxlat, coastalflow, riverflow, & |
---|
1343 | tsol_rad, temp_sol_new, qsurf, albedo, emis, z0, lon_scat_g, lat_scat_g, q2m, t2m, & |
---|
1344 | field_out_names, fields_out, field_in_names, fields_in, & |
---|
1345 | coszang) |
---|
1346 | ! coszang,soil_mc,litter_mc) |
---|
1347 | USE mod_orchidee_para |
---|
1348 | IMPLICIT NONE |
---|
1349 | |
---|
1350 | !! 0. Variable and parameter declaration |
---|
1351 | !! 0.1 Input variables |
---|
1352 | INTEGER(i_std),INTENT (in) :: kjit !! Time step number |
---|
1353 | INTEGER(i_std),INTENT (in) :: iim_glo !! Dimension of global fields |
---|
1354 | INTEGER(i_std),INTENT (in) :: jjm_glo !! Dimension of global fields |
---|
1355 | INTEGER(i_std),INTENT (in) :: kjpindex !! Number of continental points |
---|
1356 | REAL(r_std),INTENT (in) :: xrdt !! Time step in seconds |
---|
1357 | LOGICAL, INTENT (in) :: lrestart_read !! Logical for _restart_ file to read |
---|
1358 | LOGICAL, INTENT (in) :: lrestart_write !! Logical for _restart_ file to write' |
---|
1359 | REAL(r_std), INTENT (in) :: date0 !! Date at which kjit = 0 |
---|
1360 | INTEGER(i_std),DIMENSION (kjpindex), INTENT (in) :: kindex !! Index for continental points |
---|
1361 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: u !! Lowest level wind speed |
---|
1362 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: v !! Lowest level wind speed |
---|
1363 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: zlev !! Height of first layer |
---|
1364 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: qair !! Lowest level specific humidity |
---|
1365 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: precip_rain !! Rain precipitation |
---|
1366 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: precip_snow !! Snow precipitation |
---|
1367 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: lwdown !! Down-welling long-wave flux |
---|
1368 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: swnet !! Net surface short-wave flux |
---|
1369 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: swdown !! Downwelling surface short-wave flux |
---|
1370 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: temp_air !! Air temperature in Kelvin |
---|
1371 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: epot_air !! Air potential energy |
---|
1372 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: ccanopy !! CO2 concentration in the canopy |
---|
1373 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: petAcoef !! Coeficients A from the PBL resolution |
---|
1374 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: peqAcoef !! One for T and another for q |
---|
1375 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: petBcoef !! Coeficients B from the PBL resolution |
---|
1376 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: peqBcoef !! One for T and another for q |
---|
1377 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: pb !! Surface pressure |
---|
1378 | REAL(r_std),DIMENSION (kjpindex,2), INTENT(in) :: latlon !! Geographical coordinates |
---|
1379 | REAL(r_std),DIMENSION (kjpindex), INTENT(in) :: zcontfrac !! Fraction of continent |
---|
1380 | INTEGER(i_std),DIMENSION (kjpindex,8), INTENT(in) :: zneighbours !! neighbours |
---|
1381 | REAL(r_std),DIMENSION (kjpindex,2), INTENT(in) :: zresolution !! size of the grid box |
---|
1382 | REAL(r_std),DIMENSION (iim_glo,jjm_glo), INTENT(IN) :: lon_scat_g !! The scattered values for longitude |
---|
1383 | REAL(r_std),DIMENSION (iim_glo,jjm_glo), INTENT(IN) :: lat_scat_g !! The scattered values for latitude |
---|
1384 | |
---|
1385 | !! 0.2 Output variables |
---|
1386 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: z0 !! Surface roughness |
---|
1387 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: coastalflow !! Diffuse flow of water into the ocean (m^3/dt) |
---|
1388 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: riverflow !! Largest rivers flowing into the ocean (m^3/dt) |
---|
1389 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: tsol_rad !! Radiative surface temperature |
---|
1390 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: vevapp !! Total of evaporation |
---|
1391 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: temp_sol_new !! New soil temperature |
---|
1392 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: qsurf !! Surface specific humidity |
---|
1393 | REAL(r_std),DIMENSION (kjpindex,2), INTENT(out) :: albedo !! Albedo |
---|
1394 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: fluxsens !! Sensible chaleur flux |
---|
1395 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: fluxlat !! Latent chaleur flux |
---|
1396 | REAL(r_std),DIMENSION (kjpindex), INTENT(out) :: emis !! Emissivity |
---|
1397 | ! REAL(r_std),DIMENSION (kjpindex,nbdl,nstm), INTENT(inout) :: soil_mc !! soil moisture content \f($m^3 \times m^3$)\f |
---|
1398 | ! REAL(r_std),DIMENSION (kjpindex,nstm), INTENT(inout) :: litter_mc !! litter moisture content \f($m^3 \times m^3$)\f |
---|
1399 | |
---|
1400 | !! 0.3 Modified variables |
---|
1401 | REAL(r_std),DIMENSION (kjpindex), INTENT(inout) :: cdrag !! Cdrag |
---|
1402 | |
---|
1403 | !! 0.4 Optional input and output variables |
---|
1404 | REAL(r_std),DIMENSION (kjpindex), INTENT(in), OPTIONAL:: q2m !! Surface specific humidity |
---|
1405 | REAL(r_std),DIMENSION (kjpindex), INTENT(in), OPTIONAL:: t2m !! Surface air temperature |
---|
1406 | REAL(r_std), DIMENSION(kjpindex), OPTIONAL, INTENT(in):: coszang !! Cosine of the solar zenith angle (unitless) |
---|
1407 | CHARACTER(LEN=*),DIMENSION(:), OPTIONAL, INTENT(IN) :: field_in_names !! Names for deposit variables to be transported |
---|
1408 | !! from chemistry model by GCM to ORCHIDEE |
---|
1409 | REAL(r_std),DIMENSION(:,:), OPTIONAL, INTENT(IN) :: fields_in !! Fields for deposit variables to be transported |
---|
1410 | !! from chemistry model by GCM to ORCHIDEE |
---|
1411 | CHARACTER(LEN=*),DIMENSION(:), OPTIONAL, INTENT(IN) :: field_out_names !! Names for emission variables to be transported |
---|
1412 | !! to chemistry model by GCM from ORCHIDEE |
---|
1413 | REAL(r_std),DIMENSION(:,:), OPTIONAL, INTENT(OUT) :: fields_out !! Fields for emission variables to be transported |
---|
1414 | !! to chemistry model by GCM from ORCHIDEE |
---|
1415 | |
---|
1416 | !! 0.5 Local variables |
---|
1417 | REAL(r_std),DIMENSION (kjpindex) :: zccanopy !! Work array to keep ccanopy |
---|
1418 | REAL(r_std),DIMENSION (kjpindex) :: zprecip_rain !! Work array to keep precip_rain |
---|
1419 | REAL(r_std),DIMENSION (kjpindex) :: zprecip_snow !! Work array to keep precip_snow |
---|
1420 | REAL(r_std),DIMENSION (kjpindex) :: zz0 !! Work array to keep z0 |
---|
1421 | REAL(r_std),DIMENSION (kjpindex) :: zcdrag !! Work array for surface drag |
---|
1422 | REAL(r_std),DIMENSION (kjpindex) :: zcoastal !! Work array to keep coastal flow |
---|
1423 | REAL(r_std),DIMENSION (kjpindex) :: zriver !! Work array to keep river out flow |
---|
1424 | REAL(r_std),DIMENSION (kjpindex) :: znetco2 !! Work array to keep netco2flux |
---|
1425 | REAL(r_std),DIMENSION (kjpindex) :: zcarblu !! Work array to keep fco2_land_use |
---|
1426 | REAL(r_std),DIMENSION (kjpindex) :: ztsol_rad !! Work array to keep tsol_rad |
---|
1427 | REAL(r_std),DIMENSION (kjpindex) :: zvevapp !! Work array to keep vevapp |
---|
1428 | REAL(r_std),DIMENSION (kjpindex) :: ztemp_sol_new !! Work array to keep temp_sol_new |
---|
1429 | REAL(r_std),DIMENSION (kjpindex) :: zqsurf !! Work array to keep qsurf |
---|
1430 | REAL(r_std),DIMENSION (kjpindex,2) :: zalbedo !! Work array to keep albedo |
---|
1431 | REAL(r_std),DIMENSION (kjpindex) :: zfluxsens !! Work array to keep fluxsens |
---|
1432 | REAL(r_std),DIMENSION (kjpindex) :: zfluxlat !! Work array to keep fluxlat |
---|
1433 | REAL(r_std),DIMENSION (kjpindex) :: zemis !! Work array to keep emis |
---|
1434 | REAL(r_std),DIMENSION (kjpindex) :: zcoszang !! Work array to keep coszang |
---|
1435 | REAL(r_std),ALLOCATABLE, DIMENSION (:) :: soilth_lev !! Vertical soil axis for thermal scheme (m) |
---|
1436 | REAL(r_std),DIMENSION (kjpindex) :: q2m_loc !! Work array for q2m or qair |
---|
1437 | REAL(r_std),DIMENSION (kjpindex) :: t2m_loc !! Work array for t2m or temp_air |
---|
1438 | REAL(r_std),DIMENSION (:,:),ALLOCATABLE :: lon_scat !! The scattered values for longitude |
---|
1439 | REAL(r_std),DIMENSION (:,:),ALLOCATABLE :: lat_scat !! The scattered values for latitude |
---|
1440 | INTEGER(i_std) :: i, j, ik |
---|
1441 | INTEGER(i_std) :: ier |
---|
1442 | INTEGER(i_std) :: itau_sechiba |
---|
1443 | REAL(r_std) :: mx, zlev_mean |
---|
1444 | REAL(r_std), ALLOCATABLE, DIMENSION(:,:) :: tmp_lon, tmp_lat, tmp_lev |
---|
1445 | INTEGER :: old_fileout !! old Logical Int for std IO output |
---|
1446 | REAL,ALLOCATABLE,DIMENSION(:,:) :: lalo_mpi |
---|
1447 | REAL,ALLOCATABLE,DIMENSION(:) :: zlev_glo1D |
---|
1448 | REAL(r_std),DIMENSION (kjpindex) :: landpoints !! Local landpoints vector |
---|
1449 | |
---|
1450 | |
---|
1451 | CALL ipslnlf_p(new_number=numout, old_number=old_fileout) |
---|
1452 | |
---|
1453 | IF (l_first_intersurf) THEN |
---|
1454 | ! Test if q2m and t2m are present |
---|
1455 | IF (PRESENT(q2m) .AND. PRESENT(t2m)) THEN |
---|
1456 | ok_q2m_t2m=.TRUE. |
---|
1457 | ELSE |
---|
1458 | ok_q2m_t2m=.FALSE. |
---|
1459 | ENDIF |
---|
1460 | |
---|
1461 | ! Test if field_out_names and field_in_names are present and if so, count |
---|
1462 | ! the number of extra fields to exchange. |
---|
1463 | IF (PRESENT(field_out_names)) THEN |
---|
1464 | nb_fields_out=SIZE(field_out_names) |
---|
1465 | ELSE |
---|
1466 | nb_fields_out=0 |
---|
1467 | ENDIF |
---|
1468 | |
---|
1469 | IF (PRESENT(field_in_names)) THEN |
---|
1470 | nb_fields_in=SIZE(field_in_names) |
---|
1471 | ELSE |
---|
1472 | nb_fields_in=0 |
---|
1473 | ENDIF |
---|
1474 | |
---|
1475 | CALL intersurf_initialize_gathered (kjit, iim_glo, jjm_glo, kjpindex, kindex, xrdt, & |
---|
1476 | lrestart_read, lrestart_write, latlon, zcontfrac, zneighbours, zresolution, date0, & |
---|
1477 | zlev, u, v, qair, temp_air, epot_air, & |
---|
1478 | cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
1479 | precip_rain, precip_snow, lwdown, swnet, swdown, pb, & |
---|
1480 | vevapp, fluxsens, fluxlat, coastalflow, riverflow, & |
---|
1481 | tsol_rad, temp_sol_new, qsurf, albedo, emis, z0, lon_scat_g, lat_scat_g, q2m, t2m, & |
---|
1482 | field_out_names, fields_out, field_in_names, fields_in ) |
---|
1483 | |
---|
1484 | ! Return from subroutine intersurf_main_gathered |
---|
1485 | RETURN |
---|
1486 | END IF |
---|
1487 | |
---|
1488 | ! |
---|
1489 | !! Change to be in the orchidee context for XIOS |
---|
1490 | ! |
---|
1491 | CALL xios_orchidee_change_context("orchidee") |
---|
1492 | |
---|
1493 | ! |
---|
1494 | ! Shift the time step to phase the two models |
---|
1495 | ! |
---|
1496 | itau_sechiba = kjit + itau_offset |
---|
1497 | |
---|
1498 | ! Update the calendar in xios by sending the new time step |
---|
1499 | CALL xios_orchidee_update_calendar(itau_sechiba) |
---|
1500 | |
---|
1501 | CALL intsurf_time( itau_sechiba, date0_shifted ) |
---|
1502 | |
---|
1503 | ! Test LMDz inputs |
---|
1504 | IF (check_INPUTS) THEN |
---|
1505 | IF ( sec <= 7200 ) THEN |
---|
1506 | WRITE(numout,*) "sec = ",sec |
---|
1507 | CALL WriteFieldI_p("Wu",u) |
---|
1508 | WRITE(numout,*) "Lowest level wind speed :",u |
---|
1509 | CALL WriteFieldI_p("Wv",v) |
---|
1510 | WRITE(numout,*) "Lowest level wind speed :",v |
---|
1511 | CALL WriteFieldI_p("Wzlev",zlev) |
---|
1512 | WRITE(numout,*) "Height of first layer :",zlev |
---|
1513 | CALL WriteFieldI_p("Wqair",qair) |
---|
1514 | WRITE(numout,*) "Lowest level specific humidity :",qair |
---|
1515 | CALL WriteFieldI_p("Wprecip_rain",precip_rain) |
---|
1516 | WRITE(numout,*) "Rain precipitation :",precip_rain |
---|
1517 | CALL WriteFieldI_p("Wprecip_snow",precip_snow) |
---|
1518 | WRITE(numout,*) "Snow precipitation :",precip_snow |
---|
1519 | CALL WriteFieldI_p("Wlwdown",lwdown) |
---|
1520 | WRITE(numout,*) "Down-welling long-wave flux :",lwdown |
---|
1521 | CALL WriteFieldI_p("Wswnet",swnet) |
---|
1522 | WRITE(numout,*) "Net surface short-wave flux :",swnet |
---|
1523 | CALL WriteFieldI_p("Wswdown",swdown) |
---|
1524 | WRITE(numout,*) "Downwelling surface short-wave flux :",swdown |
---|
1525 | CALL WriteFieldI_p("Wtemp_air",temp_air) |
---|
1526 | WRITE(numout,*) "Air temperature in Kelvin :",temp_air |
---|
1527 | CALL WriteFieldI_p("Wepot_air",epot_air) |
---|
1528 | WRITE(numout,*) "Air potential energy :",epot_air |
---|
1529 | CALL WriteFieldI_p("Wccanopy",ccanopy) |
---|
1530 | WRITE(numout,*) "CO2 concentration in the canopy :",ccanopy |
---|
1531 | CALL WriteFieldI_p("WpetAcoef",petAcoef) |
---|
1532 | WRITE(numout,*) "Coeficients A from the PBL resolution :",petAcoef |
---|
1533 | CALL WriteFieldI_p("WpeqAcoef",peqAcoef) |
---|
1534 | WRITE(numout,*) "One for T and another for q :",peqAcoef |
---|
1535 | CALL WriteFieldI_p("WpetBcoef",petBcoef) |
---|
1536 | WRITE(numout,*) "Coeficients B from the PBL resolution :",petBcoef |
---|
1537 | CALL WriteFieldI_p("WpeqBcoef",peqBcoef) |
---|
1538 | WRITE(numout,*) "One for T and another for q :",peqBcoef |
---|
1539 | CALL WriteFieldI_p("Wcdrag",cdrag) |
---|
1540 | WRITE(numout,*) "Cdrag :",cdrag |
---|
1541 | CALL WriteFieldI_p("Wpb",pb) |
---|
1542 | WRITE(numout,*) "Surface pressure :",pb |
---|
1543 | CALL WriteFieldI_p("Wzcontfrac",zcontfrac) |
---|
1544 | WRITE(numout,*) "Fraction of continent :",zcontfrac |
---|
1545 | IF ( ok_q2m_t2m) THEN |
---|
1546 | CALL WriteFieldI_p("Wq2m",q2m) |
---|
1547 | WRITE(numout,*) "Surface specific humidity :",q2m |
---|
1548 | CALL WriteFieldI_p("Wt2m",t2m) |
---|
1549 | WRITE(numout,*) "Surface air temperature :",t2m |
---|
1550 | ENDIF |
---|
1551 | ENDIF |
---|
1552 | ENDIF |
---|
1553 | |
---|
1554 | ! |
---|
1555 | ! 1. Just change the units of some input fields |
---|
1556 | ! |
---|
1557 | DO ik=1, kjpindex |
---|
1558 | |
---|
1559 | zprecip_rain(ik) = precip_rain(ik)*xrdt |
---|
1560 | zprecip_snow(ik) = precip_snow(ik)*xrdt |
---|
1561 | zcdrag(ik) = cdrag(ik) |
---|
1562 | |
---|
1563 | ENDDO |
---|
1564 | |
---|
1565 | !>> VOC in coupled mode |
---|
1566 | IF ( PRESENT(coszang) ) THEN |
---|
1567 | zcoszang(:) = coszang(:) |
---|
1568 | ELSE |
---|
1569 | zcoszang(:) = zero |
---|
1570 | ENDIF |
---|
1571 | |
---|
1572 | IF (check_INPUTS) THEN |
---|
1573 | WRITE(numout,*) "Intersurf_main_gathered :" |
---|
1574 | WRITE(numout,*) "Time step number = ",kjit |
---|
1575 | WRITE(numout,*) "Dimension of input fields for local mpi process = ",iim_g, jj_nb |
---|
1576 | WRITE(numout,*) "Number of continental points = ",kjpindex |
---|
1577 | WRITE(numout,*) "Time step in seconds = ",xrdt |
---|
1578 | WRITE(numout,*) "Logical for _restart_ file to read, write = ",lrestart_read,lrestart_write |
---|
1579 | WRITE(numout,*) "Date at which kjit = 0 = ",date0 |
---|
1580 | WRITE(numout,*) "offset for OMP = ",offset_omp |
---|
1581 | WRITE(numout,*) "Index for continental points = ",kindex |
---|
1582 | IF (is_omp_root) THEN |
---|
1583 | WRITE(numout,*) "ROOT OMP, Index global MPI : ",kindex_mpi(:) |
---|
1584 | ENDIF |
---|
1585 | IF (is_root_prc) THEN |
---|
1586 | WRITE(numout,*) "ROOT global, Index global : ",index_g(:) |
---|
1587 | ENDIF |
---|
1588 | WRITE(numout,*) "Lowest level wind speed North = ",u |
---|
1589 | WRITE(numout,*) "Lowest level wind speed East = ",v |
---|
1590 | WRITE(numout,*) "Height of first layer = ",zlev |
---|
1591 | WRITE(numout,*) "Lowest level specific humidity = ",qair |
---|
1592 | WRITE(numout,*) "Rain precipitation = ",zprecip_rain |
---|
1593 | WRITE(numout,*) "Snow precipitation = ",zprecip_snow |
---|
1594 | WRITE(numout,*) "Down-welling long-wave flux = ",lwdown |
---|
1595 | WRITE(numout,*) "Net surface short-wave flux = ",swnet |
---|
1596 | WRITE(numout,*) "Downwelling surface short-wave flux = ",swdown |
---|
1597 | WRITE(numout,*) "Air temperature in Kelvin = ",temp_air |
---|
1598 | WRITE(numout,*) "Air potential energy = ",epot_air |
---|
1599 | WRITE(numout,*) "CO2 concentration in the canopy = ",ccanopy |
---|
1600 | WRITE(numout,*) "Coeficients A from the PBL resolution = ",petAcoef |
---|
1601 | WRITE(numout,*) "One for T and another for q = ",peqAcoef |
---|
1602 | WRITE(numout,*) "Coeficients B from the PBL resolution = ",petBcoef |
---|
1603 | WRITE(numout,*) "One for T and another for q = ",peqBcoef |
---|
1604 | WRITE(numout,*) "Cdrag = ",zcdrag |
---|
1605 | WRITE(numout,*) "Surface pressure = ",pb |
---|
1606 | WRITE(numout,*) "Geographical land coordinates lon = ", lalo(:,2) |
---|
1607 | WRITE(numout,*) "Geographical land coordinates lat = ", lalo(:,1) |
---|
1608 | WRITE(numout,*) "Fraction of continent in the grid = ",zcontfrac |
---|
1609 | ENDIF |
---|
1610 | |
---|
1611 | |
---|
1612 | ! Fields for deposit variables : to be transport from chemistry model by GCM to ORCHIDEE. |
---|
1613 | DO i = 1, nb_fields_in |
---|
1614 | WRITE(numout,*) i," Champ = ",TRIM(field_in_names(i)) |
---|
1615 | SELECT CASE(TRIM(field_in_names(i))) |
---|
1616 | CASE DEFAULT |
---|
1617 | CALL ipslerr_p (3,'intsurf_gathered', & |
---|
1618 | 'You ask in GCM an unknown field '//TRIM(field_in_names(i))//& |
---|
1619 | ' to give to ORCHIDEE for this specific version.',& |
---|
1620 | 'This model won''t be able to continue.', & |
---|
1621 | '(check your tracer parameters in GCM)') |
---|
1622 | END SELECT |
---|
1623 | ENDDO |
---|
1624 | |
---|
1625 | ! |
---|
1626 | ! 2. modification of co2 |
---|
1627 | ! |
---|
1628 | IF ( fatmco2 ) THEN |
---|
1629 | zccanopy(:) = atmco2 |
---|
1630 | WRITE (numout,*) 'Modification of the ccanopy value. CO2 = ',atmco2 |
---|
1631 | ELSE |
---|
1632 | zccanopy(:) = ccanopy(:) |
---|
1633 | ENDIF |
---|
1634 | |
---|
1635 | ! |
---|
1636 | ! 4. call sechiba for continental points only |
---|
1637 | ! |
---|
1638 | IF ( printlev_loc>=3 ) WRITE(numout,*) 'Calling sechiba' |
---|
1639 | |
---|
1640 | |
---|
1641 | IF (ok_q2m_t2m) THEN |
---|
1642 | t2m_loc=t2m |
---|
1643 | q2m_loc=q2m |
---|
1644 | ELSE |
---|
1645 | t2m_loc=temp_air |
---|
1646 | q2m_loc=qair |
---|
1647 | END IF |
---|
1648 | |
---|
1649 | CALL sechiba_main (itau_sechiba, iim_g*jj_nb, kjpindex, kindex, date0_shifted, & |
---|
1650 | lrestart_read, lrestart_write, & |
---|
1651 | lalo, contfrac, neighbours, resolution, & |
---|
1652 | zlev, u, v, qair, q2m_loc, t2m_loc, temp_air, epot_air, zccanopy, & |
---|
1653 | zcdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, & |
---|
1654 | zprecip_rain ,zprecip_snow, lwdown, swnet, swdown, zcoszang, pb, & |
---|
1655 | zvevapp, zfluxsens, zfluxlat, zcoastal, zriver, znetco2, zcarblu, & |
---|
1656 | ztsol_rad, ztemp_sol_new, zqsurf, zalbedo, zemis, zz0, & |
---|
1657 | rest_id, hist_id, hist2_id, rest_id_stom, hist_id_stom, hist_id_stom_IPCC ) |
---|
1658 | ! rest_id, hist_id, hist2_id, rest_id_stom, hist_id_stom, & |
---|
1659 | ! hist_id_stom_IPCC,soil_mc,litter_mc ) |
---|
1660 | IF ( printlev_loc>=3 ) WRITE(numout,*) 'out of SECHIBA' |
---|
1661 | |
---|
1662 | ! |
---|
1663 | ! 6. scatter output fields |
---|
1664 | ! |
---|
1665 | z0(:) = undef_sechiba |
---|
1666 | coastalflow(:) = undef_sechiba |
---|
1667 | riverflow(:) = undef_sechiba |
---|
1668 | tsol_rad(:) = undef_sechiba |
---|
1669 | vevapp(:) = undef_sechiba |
---|
1670 | temp_sol_new(:) = undef_sechiba |
---|
1671 | qsurf(:) = undef_sechiba |
---|
1672 | albedo(:,1) = undef_sechiba |
---|
1673 | albedo(:,2) = undef_sechiba |
---|
1674 | fluxsens(:) = undef_sechiba |
---|
1675 | fluxlat(:) = undef_sechiba |
---|
1676 | emis(:) = undef_sechiba |
---|
1677 | cdrag(:) = undef_sechiba |
---|
1678 | ! |
---|
1679 | |
---|
1680 | DO ik=1, kjpindex |
---|
1681 | |
---|
1682 | z0(ik) = zz0(ik) |
---|
1683 | coastalflow(ik) = zcoastal(ik) |
---|
1684 | riverflow(ik) = zriver(ik) |
---|
1685 | tsol_rad(ik) = ztsol_rad(ik) |
---|
1686 | vevapp(ik) = zvevapp(ik) |
---|
1687 | temp_sol_new(ik) = ztemp_sol_new(ik) |
---|
1688 | qsurf(ik) = zqsurf(ik) |
---|
1689 | albedo(ik,1) = zalbedo(ik,1) |
---|
1690 | albedo(ik,2) = zalbedo(ik,2) |
---|
1691 | fluxsens(ik) = zfluxsens(ik) |
---|
1692 | fluxlat(ik) = zfluxlat(ik) |
---|
1693 | emis(ik) = zemis(ik) |
---|
1694 | cdrag(ik) = zcdrag(ik) |
---|
1695 | |
---|
1696 | |
---|
1697 | |
---|
1698 | |
---|
1699 | ENDDO |
---|
1700 | |
---|
1701 | |
---|
1702 | CALL xios_orchidee_send_field("LandPoints" ,(/ ( REAL(ik), ik=1,kjpindex ) /)) |
---|
1703 | CALL xios_orchidee_send_field("Areas", area) |
---|
1704 | CALL xios_orchidee_send_field("Contfrac",contfrac) |
---|
1705 | CALL xios_orchidee_send_field("evap",zvevapp*one_day/dt_sechiba) |
---|
1706 | CALL xios_orchidee_send_field("evap_alma",zvevapp/dt_sechiba) |
---|
1707 | CALL xios_orchidee_send_field("coastalflow",zcoastal/dt_sechiba) |
---|
1708 | CALL xios_orchidee_send_field("riverflow",zriver/dt_sechiba) |
---|
1709 | CALL xios_orchidee_send_field("temp_sol_C",ztemp_sol_new-ZeroCelsius) |
---|
1710 | CALL xios_orchidee_send_field("temp_sol_K",ztemp_sol_new) |
---|
1711 | CALL xios_orchidee_send_field("fluxsens",zfluxsens) |
---|
1712 | CALL xios_orchidee_send_field("fluxlat",zfluxlat) |
---|
1713 | CALL xios_orchidee_send_field("alb_vis",zalbedo(:,1)) |
---|
1714 | CALL xios_orchidee_send_field("alb_nir",zalbedo(:,2)) |
---|
1715 | CALL xios_orchidee_send_field("tair",temp_air) |
---|
1716 | CALL xios_orchidee_send_field("qair",qair) |
---|
1717 | CALL xios_orchidee_send_field("swnet",swnet) |
---|
1718 | CALL xios_orchidee_send_field("swdown",swdown) |
---|
1719 | ! pb in hPa, output in Pa |
---|
1720 | CALL xios_orchidee_send_field("Psurf",pb*100.) |
---|
1721 | |
---|
1722 | |
---|
1723 | IF (ok_q2m_t2m) THEN |
---|
1724 | CALL xios_orchidee_send_field("t2m",t2m) |
---|
1725 | CALL xios_orchidee_send_field("q2m",q2m) |
---|
1726 | ELSE |
---|
1727 | CALL xios_orchidee_send_field("t2m",temp_air) |
---|
1728 | CALL xios_orchidee_send_field("q2m",qair) |
---|
1729 | ENDIF |
---|
1730 | |
---|
1731 | IF ( .NOT. almaoutput ) THEN |
---|
1732 | ! |
---|
1733 | ! scattered during the writing |
---|
1734 | ! |
---|
1735 | CALL histwrite_p (hist_id, 'evap', itau_sechiba, zvevapp, kjpindex, kindex) |
---|
1736 | CALL histwrite_p (hist_id, 'coastalflow',itau_sechiba, zcoastal, kjpindex, kindex) |
---|
1737 | CALL histwrite_p (hist_id, 'riverflow',itau_sechiba, zriver, kjpindex, kindex) |
---|
1738 | ! |
---|
1739 | CALL histwrite_p (hist_id, 'temp_sol', itau_sechiba, ztemp_sol_new, kjpindex, kindex) |
---|
1740 | |
---|
1741 | CALL histwrite_p (hist_id, 'tsol_max', itau_sechiba, ztemp_sol_new, kjpindex, kindex) |
---|
1742 | CALL histwrite_p (hist_id, 'tsol_min', itau_sechiba, ztemp_sol_new, kjpindex, kindex) |
---|
1743 | CALL histwrite_p (hist_id, 'fluxsens', itau_sechiba, zfluxsens, kjpindex, kindex) |
---|
1744 | CALL histwrite_p (hist_id, 'fluxlat', itau_sechiba, zfluxlat, kjpindex, kindex) |
---|
1745 | CALL histwrite_p (hist_id, 'swnet', itau_sechiba, swnet, kjpindex, kindex) |
---|
1746 | CALL histwrite_p (hist_id, 'swdown', itau_sechiba, swdown, kjpindex, kindex) |
---|
1747 | CALL histwrite_p (hist_id, 'alb_vis', itau_sechiba, zalbedo(:,1), kjpindex, kindex) |
---|
1748 | CALL histwrite_p (hist_id, 'alb_nir', itau_sechiba, zalbedo(:,2), kjpindex, kindex) |
---|
1749 | CALL histwrite_p (hist_id, 'tair', itau_sechiba, temp_air, kjpindex, kindex) |
---|
1750 | CALL histwrite_p (hist_id, 'qair', itau_sechiba, qair, kjpindex, kindex) |
---|
1751 | IF (ok_q2m_t2m) THEN |
---|
1752 | CALL histwrite_p (hist_id, 't2m', itau_sechiba, t2m, kjpindex, kindex) |
---|
1753 | CALL histwrite_p (hist_id, 'q2m', itau_sechiba, q2m, kjpindex, kindex) |
---|
1754 | ELSE |
---|
1755 | CALL histwrite_p (hist_id, 't2m', itau_sechiba, temp_air, kjpindex, kindex) |
---|
1756 | CALL histwrite_p (hist_id, 'q2m', itau_sechiba, qair, kjpindex, kindex) |
---|
1757 | ENDIF |
---|
1758 | ! |
---|
1759 | IF ( hist2_id > 0 ) THEN |
---|
1760 | CALL histwrite_p (hist2_id, 'evap', itau_sechiba, zvevapp, kjpindex, kindex) |
---|
1761 | CALL histwrite_p (hist2_id, 'coastalflow',itau_sechiba, zcoastal, kjpindex, kindex) |
---|
1762 | CALL histwrite_p (hist2_id, 'riverflow',itau_sechiba, zriver, kjpindex, kindex) |
---|
1763 | ! |
---|
1764 | CALL histwrite_p (hist2_id, 'temp_sol', itau_sechiba, temp_sol_new, kjpindex, kindex) |
---|
1765 | CALL histwrite_p (hist2_id, 'tsol_max', itau_sechiba, temp_sol_new, kjpindex, kindex) |
---|
1766 | CALL histwrite_p (hist2_id, 'tsol_min', itau_sechiba, temp_sol_new, kjpindex, kindex) |
---|
1767 | CALL histwrite_p (hist2_id, 'fluxsens', itau_sechiba, zfluxsens, kjpindex, kindex) |
---|
1768 | CALL histwrite_p (hist2_id, 'fluxlat', itau_sechiba, zfluxlat, kjpindex, kindex) |
---|
1769 | CALL histwrite_p (hist2_id, 'swnet', itau_sechiba, swnet, kjpindex, kindex) |
---|
1770 | CALL histwrite_p (hist2_id, 'swdown', itau_sechiba, swdown, kjpindex, kindex) |
---|
1771 | CALL histwrite_p (hist2_id, 'alb_vis', itau_sechiba, zalbedo(:,1), kjpindex, kindex) |
---|
1772 | CALL histwrite_p (hist2_id, 'alb_nir', itau_sechiba, zalbedo(:,2), kjpindex, kindex) |
---|
1773 | CALL histwrite_p (hist2_id, 'tair', itau_sechiba, temp_air, kjpindex, kindex) |
---|
1774 | CALL histwrite_p (hist2_id, 'qair', itau_sechiba, qair, kjpindex, kindex) |
---|
1775 | IF (ok_q2m_t2m) THEN |
---|
1776 | CALL histwrite_p (hist2_id, 't2m', itau_sechiba, t2m, kjpindex, kindex) |
---|
1777 | CALL histwrite_p (hist2_id, 'q2m', itau_sechiba, q2m, kjpindex, kindex) |
---|
1778 | ELSE |
---|
1779 | CALL histwrite_p (hist2_id, 't2m', itau_sechiba, temp_air, kjpindex, kindex) |
---|
1780 | CALL histwrite_p (hist2_id, 'q2m', itau_sechiba, qair, kjpindex, kindex) |
---|
1781 | ENDIF |
---|
1782 | ENDIF |
---|
1783 | ELSE |
---|
1784 | CALL histwrite_p (hist_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex) |
---|
1785 | CALL histwrite_p (hist_id, 'SWnet', itau_sechiba, swnet, kjpindex, kindex) |
---|
1786 | CALL histwrite_p (hist_id, 'Qh', itau_sechiba, zfluxsens, kjpindex, kindex) |
---|
1787 | CALL histwrite_p (hist_id, 'Qle', itau_sechiba, zfluxlat, kjpindex, kindex) |
---|
1788 | CALL histwrite_p (hist_id, 'AvgSurfT', itau_sechiba, ztemp_sol_new, kjpindex, kindex) |
---|
1789 | CALL histwrite_p (hist_id, 'RadT', itau_sechiba, ztemp_sol_new, kjpindex, kindex) |
---|
1790 | ! |
---|
1791 | IF ( hist2_id > 0 ) THEN |
---|
1792 | CALL histwrite_p (hist2_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex) |
---|
1793 | CALL histwrite_p (hist2_id, 'SWnet', itau_sechiba, swnet, kjpindex, kindex) |
---|
1794 | CALL histwrite_p (hist2_id, 'Qh', itau_sechiba, zfluxsens, kjpindex, kindex) |
---|
1795 | CALL histwrite_p (hist2_id, 'Qle', itau_sechiba, zfluxlat, kjpindex, kindex) |
---|
1796 | CALL histwrite_p (hist2_id, 'AvgSurfT', itau_sechiba, ztemp_sol_new, kjpindex, kindex) |
---|
1797 | CALL histwrite_p (hist2_id, 'RadT', itau_sechiba, ztemp_sol_new, kjpindex, kindex) |
---|
1798 | ENDIF |
---|
1799 | ENDIF |
---|
1800 | |
---|
1801 | ! Syncronize output but only if flag ok_histsync is set to true |
---|
1802 | IF (ok_histsync .AND. is_omp_root) THEN |
---|
1803 | IF ( (dw .EQ. xrdt) .AND. hist_id > 0 ) THEN |
---|
1804 | CALL histsync(hist_id) |
---|
1805 | ENDIF |
---|
1806 | ENDIF |
---|
1807 | |
---|
1808 | ! |
---|
1809 | ! 7. Transform the water fluxes into Kg/m^2s and m^3/s |
---|
1810 | ! |
---|
1811 | DO ik=1, kjpindex |
---|
1812 | |
---|
1813 | vevapp(ik) = vevapp(ik)/xrdt |
---|
1814 | coastalflow(ik) = coastalflow(ik)/xrdt |
---|
1815 | riverflow(ik) = riverflow(ik)/xrdt |
---|
1816 | |
---|
1817 | ENDDO |
---|
1818 | |
---|
1819 | ! Fields for emission variables : to be transport by GCM to chemistry model. |
---|
1820 | DO i = 1, nb_fields_out |
---|
1821 | SELECT CASE(TRIM(field_out_names(i))) |
---|
1822 | CASE("fCO2_land") |
---|
1823 | fields_out(:,i)=znetco2(:) |
---|
1824 | CASE("fCO2_land_use") |
---|
1825 | fields_out(:,i)=zcarblu(:) |
---|
1826 | CASE DEFAULT |
---|
1827 | CALL ipslerr_p (3,'intsurf_gathered', & |
---|
1828 | & 'You ask from GCM an unknown field '//TRIM(field_out_names(i))//& |
---|
1829 | & ' to ORCHIDEE for this specific version.',& |
---|
1830 | & 'This model won''t be able to continue.', & |
---|
1831 | & '(check your tracer parameters in GCM)') |
---|
1832 | END SELECT |
---|
1833 | ENDDO |
---|
1834 | |
---|
1835 | IF (printlev_loc >=3) WRITE (numout,*) ' intersurf_main done ' |
---|
1836 | |
---|
1837 | !Test ORCHIDEE Outputs |
---|
1838 | IF (check_INPUTS) THEN |
---|
1839 | IF ( sec <= 7200 ) THEN |
---|
1840 | CALL WriteFieldI_p("Wcdrag",cdrag) |
---|
1841 | WRITE(numout,*) "Cdrag :",cdrag |
---|
1842 | CALL WriteFieldI_p("Wz0",z0) |
---|
1843 | WRITE(numout,*) "Surface roughness :",z0 |
---|
1844 | CALL WriteFieldI_p("Wcoastalflow",coastalflow) |
---|
1845 | WRITE(numout,*) "Diffuse flow of water into the ocean (m^3/dt) :",coastalflow |
---|
1846 | CALL WriteFieldI_p("Wriverflow",riverflow) |
---|
1847 | WRITE(numout,*) "Largest rivers flowing into the ocean (m^3/dt) :",riverflow |
---|
1848 | CALL WriteFieldI_p("Wtsol_rad",tsol_rad) |
---|
1849 | WRITE(numout,*) "Radiative surface temperature :",tsol_rad |
---|
1850 | CALL WriteFieldI_p("Wvevapp",vevapp) |
---|
1851 | WRITE(numout,*) "Total of evaporation :",vevapp |
---|
1852 | CALL WriteFieldI_p("Wtemp_sol_new",temp_sol_new) |
---|
1853 | WRITE(numout,*) "New soil temperature :",temp_sol_new |
---|
1854 | CALL WriteFieldI_p("Wqsurf",qsurf) |
---|
1855 | WRITE(numout,*) "Surface specific humidity :",qsurf |
---|
1856 | CALL WriteFieldI_p("Walbedo_nir",albedo(:,1)) |
---|
1857 | WRITE(numout,*) "Albedo nir:",albedo(:,1) |
---|
1858 | CALL WriteFieldI_p("Walbedo_vis",albedo(:,2)) |
---|
1859 | WRITE(numout,*) "Albedo vir :",albedo(:,2) |
---|
1860 | CALL WriteFieldI_p("Wfluxsens",fluxsens) |
---|
1861 | WRITE(numout,*) "Sensible chaleur flux :",fluxsens |
---|
1862 | CALL WriteFieldI_p("Wfluxlat",fluxlat) |
---|
1863 | WRITE(numout,*) "Latent chaleur flux :",fluxlat |
---|
1864 | CALL WriteFieldI_p("Wemis",emis) |
---|
1865 | WRITE(numout,*) "Emissivity :",emis |
---|
1866 | ENDIF |
---|
1867 | ENDIF |
---|
1868 | ! |
---|
1869 | CALL ipslnlf_p(new_number=old_fileout) |
---|
1870 | ! |
---|
1871 | |
---|
1872 | ! |
---|
1873 | !! Finalize the XIOS orchidee context if it is the last call |
---|
1874 | ! |
---|
1875 | IF (lrestart_write) THEN |
---|
1876 | CALL xios_orchidee_context_finalize |
---|
1877 | END IF |
---|
1878 | ! |
---|
1879 | !! Change back to be in the LMDZ context for XIOS |
---|
1880 | ! |
---|
1881 | CALL xios_orchidee_change_context("LMDZ") |
---|
1882 | |
---|
1883 | |
---|
1884 | END SUBROUTINE intersurf_main_gathered |
---|
1885 | |
---|
1886 | |
---|
1887 | |
---|
1888 | !! ============================================================================================================================= |
---|
1889 | !! SUBROUTINE: intsurf_time |
---|
1890 | !! |
---|
1891 | !>\BRIEF Initalize and update time information |
---|
1892 | !! |
---|
1893 | !! DESCRIPTION: Initialize and update time information. This subroutine is called in the initialization phase and at each |
---|
1894 | !! time step from the different intersurf subroutines. |
---|
1895 | !! |
---|
1896 | !! \n |
---|
1897 | !_ ============================================================================================================================== |
---|
1898 | |
---|
1899 | SUBROUTINE intsurf_time(istp, date0) |
---|
1900 | |
---|
1901 | IMPLICIT NONE |
---|
1902 | |
---|
1903 | INTEGER(i_std), INTENT(in) :: istp !! Time step of the restart file |
---|
1904 | REAL(r_std), INTENT(in) :: date0 !! The date at which itau = 0 |
---|
1905 | |
---|
1906 | IF (l_first_intersurf) THEN |
---|
1907 | CALL ioget_calendar(calendar_str) |
---|
1908 | CALL ioget_calendar(one_year, one_day) |
---|
1909 | CALL tlen2itau('1Y',dt_sechiba,date0,year_length) |
---|
1910 | IF ( TRIM(calendar_str) .EQ. 'gregorian' ) THEN |
---|
1911 | year_spread=un |
---|
1912 | ELSE |
---|
1913 | year_spread = one_year/365.2425 |
---|
1914 | ENDIF |
---|
1915 | |
---|
1916 | IF (printlev_loc >=3) THEN |
---|
1917 | write(numout,*) "calendar_str =",calendar_str |
---|
1918 | write(numout,*) "one_year=",one_year,", one_day=",one_day |
---|
1919 | write(numout,*) "dt_sechiba=",dt_sechiba,", date0=",date0,", year_length=",year_length,", year_spread=",year_spread |
---|
1920 | ENDIF |
---|
1921 | ENDIF |
---|
1922 | |
---|
1923 | IF ( printlev_loc >=4 ) WRITE(numout,*) "---" |
---|
1924 | ! Dans diffuco (ie date0 == date0_shift !!) |
---|
1925 | |
---|
1926 | IF ( TRIM(calendar_str) .EQ. 'gregorian' ) THEN |
---|
1927 | ! |
---|
1928 | ! Get Julian date |
---|
1929 | in_julian = itau2date(istp, date0, dt_sechiba) |
---|
1930 | |
---|
1931 | ! Real date |
---|
1932 | CALL ju2ymds (in_julian, year, month, day, sec) |
---|
1933 | !!$ jur=zero |
---|
1934 | !!$ julian_diff = in_julian |
---|
1935 | !!$ month_len = ioget_mon_len (year,month) |
---|
1936 | !!$ IF ( printlev_loc >=4 ) THEN |
---|
1937 | !!$ write(numout,*) "in_julian, jur, julian_diff=",in_julian, jur, julian_diff |
---|
1938 | !!$ write(numout,*) 'DATE ymds', year, month,'(',month_len,'d)', day, sec, '-- stp --', istp |
---|
1939 | !!$ ENDIF |
---|
1940 | |
---|
1941 | ! julian number for january, the first. |
---|
1942 | CALL ymds2ju (year,1,1,zero, julian0) |
---|
1943 | julian_diff = in_julian-julian0 |
---|
1944 | ! real number of seconds |
---|
1945 | ! sec = (julian_diff-REAL(INT(julian_diff)))*one_day |
---|
1946 | sec = NINT((julian_diff-REAL(INT(julian_diff)))*one_day) |
---|
1947 | month_len = ioget_mon_len (year,month) |
---|
1948 | IF ( printlev_loc >=4 ) THEN |
---|
1949 | write(numout,*) "2 in_julian, julian0, julian_diff=",in_julian, julian0, julian_diff |
---|
1950 | write(numout,*) '2 DATE ymds', year, month,'(',month_len,'d)', day, sec, '-- stp --', istp |
---|
1951 | ENDIF |
---|
1952 | ELSE |
---|
1953 | !!$ in_julian = itau2date(istp-1, zero, dt) |
---|
1954 | !!$ CALL ju2ymds (in_julian, year, month, day, sec) |
---|
1955 | !!$ jur=zero |
---|
1956 | !!$ julian_diff = in_julian |
---|
1957 | !!$ month_len = ioget_mon_len (year,month) |
---|
1958 | !!$ IF (printlev_loc >=4) THEN |
---|
1959 | !!$ write(numout,*) "in_julian=",in_julian, jur, julian_diff |
---|
1960 | !!$ write(numout,*) 'DATE ymds', year, month,'(',month_len,'d)', day, sec, '-- stp --', istp |
---|
1961 | !!$ ENDIF |
---|
1962 | !!$ |
---|
1963 | !!$ |
---|
1964 | !!$ CALL ymds2ju (year,1,1,zero, jur) |
---|
1965 | !!$ julian_diff = in_julian-jur |
---|
1966 | !!$ CALL ju2ymds (julian_diff, year, month, day, sec) |
---|
1967 | !!$! sec = (julian_diff-REAL(INT(julian_diff)))*one_day |
---|
1968 | !!$ sec = NINT((julian_diff-REAL(INT(julian_diff)))*one_day) |
---|
1969 | !!$ month_len = ioget_mon_len (year,month) |
---|
1970 | !!$ IF (printlev_loc >=4) THEN |
---|
1971 | !!$ write(numout,*) "2 in_julian, jur, julian_diff=",in_julian, jur, julian_diff |
---|
1972 | !!$ write(numout,*) '2 DATE ymds', year, month,'(',month_len,'d)', day, sec, '-- stp --', istp |
---|
1973 | !!$ ENDIF |
---|
1974 | |
---|
1975 | !MM |
---|
1976 | !PB date0 = celui de Soenke (Ã tester avec un autre date0) |
---|
1977 | ! in_julian = itau2date(istp, 153116., dt) |
---|
1978 | in_julian = itau2date(istp, date0, dt_sechiba) |
---|
1979 | CALL itau2ymds(istp, dt_sechiba, year, month, day, sec) |
---|
1980 | CALL ymds2ju (year,1,1,zero, julian0) |
---|
1981 | julian_diff = in_julian - julian0 |
---|
1982 | month_len = ioget_mon_len (year,month) |
---|
1983 | IF (printlev_loc >=4) THEN |
---|
1984 | write(numout,*) "in_julian=",in_julian, julian0, julian_diff |
---|
1985 | write(numout,*) 'DATE ymds', year, month,'(',month_len,'d)', day, sec, '-- stp --', istp |
---|
1986 | ENDIF |
---|
1987 | ENDIF |
---|
1988 | |
---|
1989 | END SUBROUTINE intsurf_time |
---|
1990 | |
---|
1991 | END MODULE intersurf |
---|