1 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
2 | ! |
---|
3 | ! Nouveau code d'interface entre LMDZ et COSPv2 (version 2) |
---|
4 | ! L'ancienne interface s'appelait "phys_cosp2" et avait ete concue pour COSPv1.4. |
---|
5 | ! Dans cette nouvelle version de COSP, le code a ete restructure pour optimiser les calculs |
---|
6 | ! des differents simulateurs et pour proposer de nouvelles fonctionnalites (par exemple, |
---|
7 | ! intervenir sur les profils sous-maille, ou subcolumns, donnes en entre a COSP afin que |
---|
8 | ! leur definition soit coherente avec les parametrisations du modele hote). |
---|
9 | ! Cette version de COSP propose aussi de nombreux nouveaux diagnostics, notamment pour |
---|
10 | ! le simulateur lidar (diagnostics CALIPSO-OPAQ, lidar sol 532nm et lidar ATLID 355nm). |
---|
11 | ! |
---|
12 | ! Interface reecrite par R.Guzman (01/2019), a partir de l'interface initiale concue |
---|
13 | ! et ecrite par A.Idelkadi |
---|
14 | ! |
---|
15 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
16 | ! subroutine phys_cosp2( itap,dtime,freq_cosp, & |
---|
17 | subroutine lmdz_cosp_interface(itap, dtime, freq_cosp, ok_mensuelCOSP, ok_journeCOSP, & |
---|
18 | ok_hfCOSP, ecrit_mth, ecrit_day, ecrit_hf, ok_all_xml, & |
---|
19 | missing_val, Nptslmdz, Nlevlmdz, lon, lat, presnivs, & |
---|
20 | overlaplmdz, sunlit, ref_liq, ref_ice, fracTerLic, & |
---|
21 | u_wind, v_wind, phis, phi, ph, p, skt, t, sh, rh, & |
---|
22 | tca, cca, mr_lsliq, mr_lsice, fl_lsrainI, fl_lssnowI, & |
---|
23 | fl_ccrainI, fl_ccsnowI, mr_ozone, dtau_s, dem_s) |
---|
24 | |
---|
25 | !-------------- Inputs --------------- |
---|
26 | ! itap, !Increment de la physiq |
---|
27 | ! dtime, !Pas de temps physiq |
---|
28 | ! overlaplmdz, !Type Overlap venant de LMDZ |
---|
29 | ! Npoints, !Nb de points de la grille physiq |
---|
30 | ! Nlevels, !Nb de niveaux verticaux |
---|
31 | ! Ncolumns, !Number of subcolumns |
---|
32 | ! lon,lat, !Longitudes et latitudes de la grille LMDZ |
---|
33 | ! ref_liq, ref_ice, !Rayons effectifs des particules liq et ice (en micron) |
---|
34 | ! fracTerLic, !Fraction terre a convertir en masque |
---|
35 | ! u_wind, v_wind, !Vents a 10m ??? |
---|
36 | ! phi, !Geopotentiel |
---|
37 | ! phis, !Geopotentiel sol |
---|
38 | ! ph, !pression pour chaque inter-couche |
---|
39 | ! p, !Pression aux milieux des couches |
---|
40 | ! skt, t, !Temp au sol et temp 3D |
---|
41 | ! sh, !Humidite specifique |
---|
42 | ! rh, !Humidite relative |
---|
43 | ! tca, !Fraction nuageuse |
---|
44 | ! cca !Fraction nuageuse convective |
---|
45 | ! mr_lsliq, !Liq Cloud water content |
---|
46 | ! mr_lsice, !Ice Cloud water content |
---|
47 | ! mr_ccliq, !Convective Cloud Liquid water content |
---|
48 | ! mr_ccice, !Cloud ice water content |
---|
49 | ! fl_lsrain, !Large scale precipitation lic |
---|
50 | ! fl_lssnow, !Large scale precipitation ice |
---|
51 | ! fl_ccrain, !Convective precipitation lic |
---|
52 | ! fl_ccsnow, !Convective precipitation ice |
---|
53 | ! mr_ozone, !Concentration ozone (Kg/Kg) |
---|
54 | ! dem_s !Cloud optical emissivity |
---|
55 | ! dtau_s !Cloud optical thickness |
---|
56 | ! emsfc_lw = 1. !Surface emissivity dans radlwsw.F90 |
---|
57 | |
---|
58 | |
---|
59 | !-------------- Outputs -------------- |
---|
60 | ! La liste complete des diagnostics de sortie (observables simulees) que l'on peut |
---|
61 | ! avoir avec COSPv2 se trouve au debut du fichier : cosp_read_otputkeys.F90 |
---|
62 | |
---|
63 | |
---|
64 | !!! Modules specifiques a l'interface LMDZ-COSP |
---|
65 | use mod_phys_lmdz_para |
---|
66 | use mod_grid_phy_lmdz |
---|
67 | use ioipsl |
---|
68 | use iophy |
---|
69 | use lmdz_xios, ONLY : using_xios |
---|
70 | use lmdz_cosp_output_mod |
---|
71 | use lmdz_cosp_output_write_mod |
---|
72 | use lmdz_cosp_read_outputkeys |
---|
73 | use lmdz_cosp_subsample_and_optics_mod, only : subsample_and_optics |
---|
74 | use lmdz_cosp_construct_destroy_mod |
---|
75 | |
---|
76 | !!! Modules faisant partie du code source de COSPv2 |
---|
77 | use cosp_kinds, only: wp |
---|
78 | use MOD_COSP_CONFIG, only: N_HYDRO,RTTOV_MAX_CHANNELS, & |
---|
79 | niv_sorties, vgrid_z_in |
---|
80 | use mod_quickbeam_optics, only: size_distribution,hydro_class_init, & |
---|
81 | quickbeam_optics_init |
---|
82 | use quickbeam, only: radar_cfg |
---|
83 | use mod_cosp, only: cosp_init,cosp_optical_inputs, & |
---|
84 | cosp_column_inputs,cosp_outputs, & |
---|
85 | cosp_simulator |
---|
86 | |
---|
87 | |
---|
88 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
89 | ! |
---|
90 | ! Declaration des variables |
---|
91 | ! |
---|
92 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
93 | |
---|
94 | IMPLICIT NONE |
---|
95 | |
---|
96 | ! Local variables |
---|
97 | character(len=64),PARAMETER :: cosp_input_nl = 'cospv2_input_nl.txt' |
---|
98 | character(len=64),PARAMETER :: cosp_output_nl = 'cospv2_output_nl.txt' |
---|
99 | |
---|
100 | integer, save :: isccp_topheight, isccp_topheight_direction, overlap |
---|
101 | integer, save :: Ncolumns ! Number of subcolumns in SCOPS |
---|
102 | integer, save :: Npoints ! Number of gridpoints |
---|
103 | !$OMP THREADPRIVATE(Npoints) |
---|
104 | integer, save :: Nlevels ! Number of model vertical levels |
---|
105 | integer :: Nptslmdz, Nlevlmdz ! Nb de points issus de physiq.F |
---|
106 | integer, save :: Npoints_it ! Max number of gridpoints to be |
---|
107 | ! processed in one iteration |
---|
108 | type(cosp_config), save :: cfg ! Variable qui contient les cles |
---|
109 | ! logiques des simulateurs et des |
---|
110 | ! diagnostics, definie dans: |
---|
111 | ! lmdz_cosp_construct_destroy_mod |
---|
112 | !$OMP THREADPRIVATE(cfg) |
---|
113 | |
---|
114 | integer :: t0, t1, count_rate, count_max |
---|
115 | real(wp), save :: cloudsat_radar_freq, cloudsat_k2, rttov_ZenAng, co2, & |
---|
116 | ch4, n2o, co, emsfc_lw |
---|
117 | !$OMP THREADPRIVATE(emsfc_lw) |
---|
118 | |
---|
119 | integer, dimension(RTTOV_MAX_CHANNELS), save :: rttov_Channels |
---|
120 | real(wp), dimension(RTTOV_MAX_CHANNELS), save :: rttov_Surfem |
---|
121 | integer, save :: surface_radar, use_mie_tables, & |
---|
122 | cloudsat_use_gas_abs, cloudsat_do_ray, & |
---|
123 | melt_lay |
---|
124 | integer, save :: lidar_ice_type |
---|
125 | integer, save :: rttov_platform, rttov_satellite, & |
---|
126 | rttov_Instrument, rttov_Nchannels |
---|
127 | logical, save :: use_vgrid_in, csat_vgrid_in, & |
---|
128 | use_precipitation_fluxes |
---|
129 | |
---|
130 | ! Declaration necessaires pour les sorties IOIPSL |
---|
131 | real :: ecrit_day, ecrit_hf, ecrit_mth, missing_val |
---|
132 | logical :: ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, ok_all_xml |
---|
133 | logical, save :: debut_cosp=.true. |
---|
134 | !$OMP THREADPRIVATE(debut_cosp) |
---|
135 | |
---|
136 | logical, save :: first_write=.true. |
---|
137 | !$OMP THREADPRIVATE(first_write) |
---|
138 | |
---|
139 | integer, save :: cosp_init_flag = 0 |
---|
140 | !$OMP THREADPRIVATE(cosp_init_flag) |
---|
141 | |
---|
142 | |
---|
143 | !----------------------------- Input variables from LMDZ-GCM ------------------------------- |
---|
144 | integer :: overlaplmdz ! overlap type: 1=max, |
---|
145 | ! 2=rand, 3=max/rand |
---|
146 | real, dimension(Nptslmdz,Nlevlmdz) :: phi, p, ph, T, sh, rh, tca, cca, mr_lsliq, & |
---|
147 | mr_lsice, mr_ccliq, mr_ccice, fl_lsrain, & |
---|
148 | fl_lssnow, fl_ccrain, fl_ccsnow, fl_lsgrpl, & |
---|
149 | zlev, zlev_half, mr_ozone, radliq, radice, & |
---|
150 | dtau_s, dem_s, dtau_c, dem_c, ref_liq, ref_ice |
---|
151 | real, dimension(Nptslmdz,Nlevlmdz) :: fl_lsrainI, fl_lssnowI, fl_ccrainI, fl_ccsnowI |
---|
152 | real, dimension(Nptslmdz) :: lon, lat, skt, fracTerLic, u_wind, v_wind, & |
---|
153 | phis, sunlit |
---|
154 | real, dimension(Nptslmdz) :: land ! variables intermediaire pour masque TerLic |
---|
155 | real, dimension(Nlevlmdz) :: presnivs |
---|
156 | integer :: itap, k, ip |
---|
157 | real :: dtime, freq_cosp |
---|
158 | real, dimension(2) :: time_bnds |
---|
159 | |
---|
160 | double precision :: d_dtime |
---|
161 | double precision, dimension(2) :: d_time_bnds |
---|
162 | |
---|
163 | |
---|
164 | ! ###################################################################################### |
---|
165 | ! Declarations specific to COSP2 |
---|
166 | ! ###################################################################################### |
---|
167 | |
---|
168 | ! Local variables |
---|
169 | logical :: & |
---|
170 | Lsingle = .true., & ! True if using MMF_v3_single_moment CLOUDSAT |
---|
171 | ! microphysical scheme (default) |
---|
172 | Ldouble = .false. ! True if using MMF_v3.5_two_moment CLOUDSAT |
---|
173 | ! microphysical scheme |
---|
174 | type(size_distribution), save :: sd ! Hydrometeor description |
---|
175 | !$OMP THREADPRIVATE(sd) |
---|
176 | type(radar_cfg), save :: rcfg_cloudsat ! Radar configuration |
---|
177 | !$OMP THREADPRIVATE(rcfg_cloudsat) |
---|
178 | real, dimension(Nptslmdz,Nlevlmdz,N_HYDRO) :: Reff ! Liquid and Ice particles |
---|
179 | ! effective radius |
---|
180 | type(cosp_outputs) :: cospOUT ! COSP simulator outputs |
---|
181 | type(cosp_optical_inputs) :: cospIN ! COSP optical (or derived?) |
---|
182 | ! fields needed by simulators |
---|
183 | type(cosp_column_inputs) :: cospstateIN ! COSP model fields needed |
---|
184 | ! by simulators |
---|
185 | character(len=256), dimension(100) :: cosp_status |
---|
186 | character(len=64), save :: cloudsat_micro_scheme |
---|
187 | |
---|
188 | ! Indices to address arrays of LS and CONV hydrometeors |
---|
189 | integer,parameter :: & |
---|
190 | I_LSCLIQ = 1, & ! Large-scale (stratiform) liquid |
---|
191 | I_LSCICE = 2, & ! Large-scale (stratiform) ice |
---|
192 | I_LSRAIN = 3, & ! Large-scale (stratiform) rain |
---|
193 | I_LSSNOW = 4, & ! Large-scale (stratiform) snow |
---|
194 | I_CVCLIQ = 5, & ! Convective liquid |
---|
195 | I_CVCICE = 6, & ! Convective ice |
---|
196 | I_CVRAIN = 7, & ! Convective rain |
---|
197 | I_CVSNOW = 8, & ! Convective snow |
---|
198 | I_LSGRPL = 9 ! Large-scale (stratiform) groupel |
---|
199 | |
---|
200 | ! Parametres qui sont lus a partir du fichier "cosp_input_nl.txt" |
---|
201 | namelist/COSP_INPUT/overlap, isccp_topheight, isccp_topheight_direction, & |
---|
202 | npoints_it, ncolumns, use_vgrid_in, csat_vgrid_in, & |
---|
203 | cloudsat_radar_freq, surface_radar, use_mie_tables, & |
---|
204 | cloudsat_use_gas_abs, cloudsat_do_ray, melt_lay, cloudsat_k2, & |
---|
205 | cloudsat_micro_scheme, lidar_ice_type, use_precipitation_fluxes, & |
---|
206 | rttov_platform, rttov_satellite, rttov_Instrument, rttov_Nchannels, & |
---|
207 | rttov_Channels, rttov_Surfem, rttov_ZenAng, co2, ch4, n2o, co |
---|
208 | |
---|
209 | !------------------------ Fin declaration des variables ------------------------ |
---|
210 | |
---|
211 | |
---|
212 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
213 | ! |
---|
214 | ! 1) Lecture du fichier "cosp_input_nl.txt", parametres d'entree pour COSP |
---|
215 | ! |
---|
216 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
217 | |
---|
218 | print*,'Entree lmdz_cosp_interface' !phys_cosp2' |
---|
219 | if (debut_cosp) then |
---|
220 | NPoints=Nptslmdz |
---|
221 | Nlevels=Nlevlmdz |
---|
222 | ! Surface emissivity |
---|
223 | emsfc_lw = 1. |
---|
224 | |
---|
225 | ! Lecture du namelist input |
---|
226 | ! CALL read_cosp_input |
---|
227 | IF (is_master) THEN |
---|
228 | OPEN(10,file=cosp_input_nl,status='old') |
---|
229 | READ(10,nml=cosp_input) |
---|
230 | CLOSE(10) |
---|
231 | ENDIF |
---|
232 | |
---|
233 | |
---|
234 | !$OMP BARRIER |
---|
235 | CALL bcast(overlap) |
---|
236 | CALL bcast(isccp_topheight) |
---|
237 | CALL bcast(isccp_topheight_direction) |
---|
238 | CALL bcast(npoints_it) |
---|
239 | CALL bcast(ncolumns) |
---|
240 | CALL bcast(use_vgrid_in) |
---|
241 | CALL bcast(csat_vgrid_in) |
---|
242 | CALL bcast(cloudsat_radar_freq) |
---|
243 | CALL bcast(surface_radar) |
---|
244 | CALL bcast(cloudsat_use_gas_abs) |
---|
245 | CALL bcast(cloudsat_do_ray) |
---|
246 | CALL bcast(cloudsat_k2) |
---|
247 | CALL bcast(lidar_ice_type) |
---|
248 | CALL bcast(use_precipitation_fluxes) |
---|
249 | CALL bcast(rttov_platform) |
---|
250 | CALL bcast(rttov_satellite) |
---|
251 | CALL bcast(rttov_Instrument) |
---|
252 | CALL bcast(rttov_Nchannels) |
---|
253 | CALL bcast(rttov_Channels) |
---|
254 | CALL bcast(rttov_Surfem) |
---|
255 | CALL bcast(rttov_ZenAng) |
---|
256 | CALL bcast(co2) |
---|
257 | CALL bcast(ch4) |
---|
258 | CALL bcast(n2o) |
---|
259 | CALL bcast(co) |
---|
260 | CALL bcast(cloudsat_micro_scheme) |
---|
261 | |
---|
262 | print*,'ok read cosp_input_nl' |
---|
263 | |
---|
264 | ! Clefs Outputs initialisation |
---|
265 | IF (using_xios) THEN |
---|
266 | call cosp_outputkeys_init(cfg) |
---|
267 | ELSE |
---|
268 | call read_cosp_output_nl(itap,cosp_output_nl,cfg) |
---|
269 | ENDIF |
---|
270 | |
---|
271 | print*,' Cles des differents simulateurs cosp a itap :',itap |
---|
272 | print*,'cfg%Lcloudsat, cfg%Lcalipso, cfg%LgrLidar532, cfg%Latlid, cfg%Lparasol, & |
---|
273 | cfg%Lisccp, cfg%Lmisr, cfg%Lmodis, cfg%Lrttov', & |
---|
274 | cfg%Lcloudsat, cfg%Lcalipso, cfg%LgrLidar532, cfg%Latlid, cfg%Lparasol, & |
---|
275 | cfg%Lisccp, cfg%Lmisr, cfg%Lmodis, cfg%Lrttov |
---|
276 | |
---|
277 | if (overlaplmdz.ne.overlap) then |
---|
278 | print*,'Attention overlaplmdz different de overlap lu dans namelist ' |
---|
279 | endif |
---|
280 | |
---|
281 | IF (using_xios) THEN |
---|
282 | print*,'On passe par using_xios' |
---|
283 | ELSE |
---|
284 | if (cosp_init_flag .eq. 0) then |
---|
285 | |
---|
286 | ! Initialize the distributional parameters for hydrometeors in radar simulator. |
---|
287 | ! In COSPv1.4, this was declared in cosp_defs.f. |
---|
288 | if (cloudsat_micro_scheme == 'MMF_v3.5_two_moment') then |
---|
289 | ldouble = .true. |
---|
290 | lsingle = .false. |
---|
291 | endif |
---|
292 | call hydro_class_init(lsingle,ldouble,sd) |
---|
293 | call quickbeam_optics_init() |
---|
294 | |
---|
295 | print*,' just before call COSP_INIT, cosp_init_flag =', cosp_init_flag |
---|
296 | call COSP_INIT(cfg%Lisccp, cfg%Lmodis, cfg%Lmisr, cfg%Lcloudsat, cfg%Lcalipso, & |
---|
297 | cfg%LgrLidar532, cfg%Latlid, cfg%Lparasol, cfg%Lrttov, & |
---|
298 | cloudsat_radar_freq, cloudsat_k2, cloudsat_use_gas_abs, & |
---|
299 | cloudsat_do_ray, isccp_topheight, isccp_topheight_direction, & |
---|
300 | surface_radar, rcfg_cloudsat, use_vgrid_in, csat_vgrid_in, & |
---|
301 | niv_sorties, Nlevels, cloudsat_micro_scheme) |
---|
302 | cosp_init_flag = 1 |
---|
303 | print*,' just after call COSP_INIT, cosp_init_flag =', cosp_init_flag |
---|
304 | endif |
---|
305 | ENDIF |
---|
306 | |
---|
307 | print*,'Fin lecture Namelists, debut_cosp =',debut_cosp |
---|
308 | |
---|
309 | endif ! debut_cosp |
---|
310 | |
---|
311 | |
---|
312 | !!! Ici on modifie les cles logiques pour les outputs selon les champs actives dans les .xml |
---|
313 | if ((itap.ge.1).and.(first_write))then |
---|
314 | IF (using_xios) call read_xiosfieldactive(cfg) |
---|
315 | first_write=.false. |
---|
316 | |
---|
317 | if (cosp_init_flag .eq. 0) then |
---|
318 | |
---|
319 | ! Initialize the distributional parameters for hydrometeors in radar simulator. |
---|
320 | ! In COSPv1.4, this was declared in cosp_defs.f. |
---|
321 | if (cloudsat_micro_scheme == 'MMF_v3.5_two_moment') then |
---|
322 | ldouble = .true. |
---|
323 | lsingle = .false. |
---|
324 | endif |
---|
325 | call hydro_class_init(lsingle,ldouble,sd) |
---|
326 | call quickbeam_optics_init() |
---|
327 | |
---|
328 | print*,' just before call COSP_INIT, cosp_init_flag =', cosp_init_flag |
---|
329 | call COSP_INIT(cfg%Lisccp, cfg%Lmodis, cfg%Lmisr, cfg%Lcloudsat, cfg%Lcalipso, & |
---|
330 | cfg%LgrLidar532, cfg%Latlid, cfg%Lparasol, cfg%Lrttov, & |
---|
331 | cloudsat_radar_freq, cloudsat_k2, cloudsat_use_gas_abs, & |
---|
332 | cloudsat_do_ray, isccp_topheight, isccp_topheight_direction, & |
---|
333 | surface_radar, rcfg_cloudsat, use_vgrid_in, csat_vgrid_in, & |
---|
334 | niv_sorties, Nlevels, cloudsat_micro_scheme) |
---|
335 | cosp_init_flag = 1 |
---|
336 | print*,' just after call COSP_INIT, cosp_init_flag =', cosp_init_flag |
---|
337 | endif ! cosp_init_flag |
---|
338 | |
---|
339 | |
---|
340 | print*,' Cles des differents simulateurs cosp a itap :',itap |
---|
341 | print*,'cfg%Lcloudsat, cfg%Lcalipso, cfg%LgrLidar532, cfg%Latlid, cfg%Lparasol, & |
---|
342 | cfg%Lisccp, cfg%Lmisr, cfg%Lmodis, cfg%Lrttov', & |
---|
343 | cfg%Lcloudsat, cfg%Lcalipso, cfg%LgrLidar532, cfg%Latlid, cfg%Lparasol, & |
---|
344 | cfg%Lisccp, cfg%Lmisr, cfg%Lmodis, cfg%Lrttov |
---|
345 | |
---|
346 | endif !(itap.gt.1).and.(first_write) |
---|
347 | |
---|
348 | time_bnds(1) = dtime-dtime/2. |
---|
349 | time_bnds(2) = dtime+dtime/2. |
---|
350 | |
---|
351 | d_time_bnds=time_bnds |
---|
352 | d_dtime=dtime |
---|
353 | |
---|
354 | !------------------------- Fin initialisation de COSP -------------------------- |
---|
355 | |
---|
356 | |
---|
357 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
358 | ! |
---|
359 | ! 3) Calculs des champs d'entree COSP a partir des variables LMDZ |
---|
360 | ! |
---|
361 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
362 | |
---|
363 | ! 0) Create ptop/ztop for gbx%pf and gbx%zlev are for the the interface, |
---|
364 | ! also reverse CAM height/pressure values for input into CSOP |
---|
365 | ! CAM state%pint from top to surface, COSP wants surface to top. |
---|
366 | |
---|
367 | ! 0) Altitudes du modele calculees a partir de la variable geopotentiel phi et phis |
---|
368 | zlev = phi/9.81 |
---|
369 | |
---|
370 | zlev_half(:,1) = phis(:)/9.81 |
---|
371 | do k = 2, Nlevels |
---|
372 | do ip = 1, Npoints |
---|
373 | zlev_half(ip,k) = phi(ip,k)/9.81 + & |
---|
374 | (phi(ip,k)-phi(ip,k-1))/9.81 * (ph(ip,k)-p(ip,k)) / (p(ip,k)-p(ip,k-1)) |
---|
375 | enddo |
---|
376 | enddo |
---|
377 | |
---|
378 | ! 1) Quantite de nuages (couverture?), convectif (=0) et total |
---|
379 | cca = 0._wp ! convective_cloud_amount (1) |
---|
380 | tca = tca ! total_cloud_amount (1) |
---|
381 | |
---|
382 | ! 2) Humidite relative est donnee tel quel (variable rh) |
---|
383 | |
---|
384 | ! 3) Masque terre/mer a partir de la variable fracTerLic |
---|
385 | do ip = 1, Npoints |
---|
386 | if (fracTerLic(ip).ge.0.5) then |
---|
387 | land(ip) = 1. |
---|
388 | else |
---|
389 | land(ip) = 0. |
---|
390 | endif |
---|
391 | enddo |
---|
392 | |
---|
393 | |
---|
394 | ! A voir l equivalent LMDZ |
---|
395 | mr_ccliq = 0.0 |
---|
396 | mr_ccice = 0.0 |
---|
397 | !!! gbx%mr_hydro(:,:,I_LSCLIQ) = mr_lsliq !mixing_ratio_large_scale_cloud_liquid (kg/kg) |
---|
398 | !!! gbx%mr_hydro(:,:,I_LSCICE) = mr_lsice !mixing_ratio_large_scale_cloud_ic |
---|
399 | !!! gbx%mr_hydro(:,:,I_CVCLIQ) = mr_ccliq !mixing_ratio_convective_cloud_liquid |
---|
400 | !!! gbx%mr_hydro(:,:,I_CVCICE) = mr_ccice !mixing_ratio_convective_cloud_ice |
---|
401 | ! A revoir |
---|
402 | fl_lsrain = fl_lsrainI + fl_ccrainI |
---|
403 | fl_lssnow = fl_lssnowI + fl_ccsnowI |
---|
404 | !!! gbx%rain_ls = fl_lsrain !flux_large_scale_cloud_rain (kg m^-2 s^-1) |
---|
405 | !!! gbx%snow_ls = fl_lssnow !flux_large_scale_cloud_snow |
---|
406 | ! A voir l equivalent LMDZ |
---|
407 | fl_lsgrpl = 0. |
---|
408 | fl_ccsnow = 0. |
---|
409 | fl_ccrain = 0. |
---|
410 | !!! gbx%grpl_ls = fl_lsgrpl !flux_large_scale_cloud_graupel |
---|
411 | !!! gbx%rain_cv = fl_ccrain !flux_convective_cloud_rain |
---|
412 | !!! gbx%snow_cv = fl_ccsnow !flux_convective_cloud_snow |
---|
413 | |
---|
414 | ! ISCCP simulator |
---|
415 | dtau_c = 0. |
---|
416 | dem_c = 0. |
---|
417 | |
---|
418 | ! note: reff_cosp dimensions should be same as cosp (reff_cosp has 9 hydrometeor dimension) |
---|
419 | Reff(1:Npoints,1:Nlevels,1:N_HYDRO) = 0. |
---|
420 | Reff(:,:,I_LSCLIQ) = ref_liq*1e-6 |
---|
421 | Reff(:,:,I_LSCICE) = ref_ice*1e-6 |
---|
422 | Reff(:,:,I_CVCLIQ) = ref_liq*1e-6 |
---|
423 | Reff(:,:,I_CVCICE) = ref_ice*1e-6 |
---|
424 | |
---|
425 | |
---|
426 | if (cosp_init_flag .eq. 1) then ! cosp_init_flag = 1 |
---|
427 | |
---|
428 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
429 | ! |
---|
430 | ! 4a) On construit la variable cospOUT qui contient tous les diagnostics de sortie. |
---|
431 | ! Elle sera remplie lors de l'appel du simulateur COSP |
---|
432 | ! |
---|
433 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
434 | |
---|
435 | call construct_cosp_outputs(cfg,Npoints,Ncolumns,Nlevels,niv_sorties,0,cospOUT) |
---|
436 | |
---|
437 | |
---|
438 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
439 | ! |
---|
440 | ! 4b) On construit la variable cospstateIN que l'on va remplir avec les champs LMDZ |
---|
441 | ! Les champ verticaux doivent etre donnes a l'envers, c-a-d : (Nlevels:1) = (TOA:SFC) |
---|
442 | ! |
---|
443 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
444 | |
---|
445 | call construct_cospstateIN(Npoints,Nlevels,0,cospstateIN) |
---|
446 | |
---|
447 | cospstateIN%lat = lat(1:Npoints) |
---|
448 | cospstateIN%lon = lon(1:Npoints) |
---|
449 | cospstateIN%at = t(1:Npoints,Nlevels:1:-1) |
---|
450 | cospstateIN%qv = sh(1:Npoints,Nlevels:1:-1) |
---|
451 | cospstateIN%o3 = mr_ozone(1:Npoints,Nlevels:1:-1) |
---|
452 | cospstateIN%sunlit = sunlit(1:Npoints) |
---|
453 | cospstateIN%skt = skt(1:Npoints) |
---|
454 | cospstateIN%land = land(1:Npoints) |
---|
455 | cospstateIN%surfelev = zlev_half(1:Npoints,1) |
---|
456 | cospstateIN%pfull = p(1:Npoints,Nlevels:1:-1) |
---|
457 | cospstateIN%phalf(1:Npoints,1) = 0._wp |
---|
458 | cospstateIN%phalf(1:Npoints,2:Nlevels+1) = ph(1:Npoints,Nlevels:1:-1) |
---|
459 | cospstateIN%hgt_matrix = zlev(1:Npoints,Nlevels:1:-1) |
---|
460 | cospstateIN%hgt_matrix_half(1:Npoints,Nlevels+1) = 0._wp |
---|
461 | cospstateIN%hgt_matrix_half(1:Npoints,1:Nlevels) = zlev_half(1:Npoints,Nlevels:1:-1) |
---|
462 | |
---|
463 | |
---|
464 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
465 | ! |
---|
466 | ! 4c) On construit la variable cospIN qui contient les proprietes optiques subcolumn |
---|
467 | ! pour COSP. Elle sera essentiellement remplie dans la subroutine subsample_and_optics |
---|
468 | ! ou sont appeles SCOPS, PREC_SCOPS et les subroutines qui calculent les signaux |
---|
469 | ! simules pour chaque simulateur actif. |
---|
470 | ! |
---|
471 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
472 | |
---|
473 | call construct_cospIN(cfg,Npoints,Ncolumns,Nlevels,cospIN) |
---|
474 | cospIN%emsfc_lw = emsfc_lw |
---|
475 | if (cfg%Lcloudsat) cospIN%rcfg_cloudsat = rcfg_cloudsat |
---|
476 | |
---|
477 | |
---|
478 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
479 | ! |
---|
480 | ! 5) Appel de subsample_and_optics : Les champs verticaux doivent etre donnes a |
---|
481 | ! l'envers comme pour le remplissage de cospstateIN, c-a-d : (Nlevels:1) = (TOA:SFC) |
---|
482 | ! |
---|
483 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
484 | |
---|
485 | call subsample_and_optics(cfg, Npoints, Nlevels, Ncolumns, N_HYDRO,overlap, & |
---|
486 | use_precipitation_fluxes, lidar_ice_type, sd, & |
---|
487 | tca(1:Npoints,Nlevels:1:-1), cca(1:Npoints,Nlevels:1:-1), & |
---|
488 | fl_lsrain(1:Npoints,Nlevels:1:-1), & |
---|
489 | fl_lssnow(1:Npoints,Nlevels:1:-1), & |
---|
490 | fl_lsgrpl(1:Npoints,Nlevels:1:-1), & |
---|
491 | fl_ccrain(1:Npoints,Nlevels:1:-1), & |
---|
492 | fl_ccsnow(1:Npoints,Nlevels:1:-1), & |
---|
493 | mr_lsliq(1:Npoints,Nlevels:1:-1), & |
---|
494 | mr_lsice(1:Npoints,Nlevels:1:-1), & |
---|
495 | mr_ccliq(1:Npoints,Nlevels:1:-1), & |
---|
496 | mr_ccice(1:Npoints,Nlevels:1:-1), & |
---|
497 | Reff(1:Npoints,Nlevels:1:-1,:), & |
---|
498 | dtau_c(1:Npoints,Nlevels:1:-1), & |
---|
499 | dtau_s(1:Npoints,Nlevels:1:-1), & |
---|
500 | dem_c(1:Npoints,Nlevels:1:-1), & |
---|
501 | dem_s(1:Npoints,Nlevels:1:-1), cospstateIN, cospIN) |
---|
502 | |
---|
503 | |
---|
504 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
505 | ! |
---|
506 | ! 6) On appelle le simulateur COSPv2 |
---|
507 | ! |
---|
508 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
509 | |
---|
510 | print*,'call simulateur' |
---|
511 | |
---|
512 | cosp_status = COSP_SIMULATOR(cospIN, cospstateIN, cospOUT, 1, Npoints, debug=.false.) |
---|
513 | |
---|
514 | endif ! cosp_init_flag = 1 |
---|
515 | |
---|
516 | |
---|
517 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
518 | ! |
---|
519 | ! 7a) Ecriture des sorties 1: on cree d'abord les fichiers NCDF pour ecrire les sorties |
---|
520 | ! en appelant lmdz_cosp_output_open (lors du premier appel de cette interface pour les |
---|
521 | ! 2 options d'ecriture), ou sont definis les axes et les caracteristiques |
---|
522 | ! des fichiers de sortie avec les diagnostics. |
---|
523 | ! |
---|
524 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
525 | |
---|
526 | if (debut_cosp) then |
---|
527 | !$OMP MASTER |
---|
528 | |
---|
529 | print *, ' Open outpts files and define axis' |
---|
530 | call lmdz_cosp_output_open(Nlevlmdz, Ncolumns, presnivs, dtime, freq_cosp, & |
---|
531 | ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, ok_all_xml, & |
---|
532 | ecrit_mth, ecrit_day, ecrit_hf, use_vgrid_in, & |
---|
533 | niv_sorties, vgrid_z_in, zlev(1,:)) |
---|
534 | |
---|
535 | !$OMP END MASTER |
---|
536 | !$OMP BARRIER |
---|
537 | debut_cosp=.false. |
---|
538 | endif ! debut_cosp |
---|
539 | |
---|
540 | if (cosp_init_flag .eq. 1) then |
---|
541 | |
---|
542 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
543 | ! |
---|
544 | ! 7b) Ecriture des sorties 2: le remplissage des fichiers de sortie se fait a chaque |
---|
545 | ! appel de cette interface avec une difference entre les 2 options d'ecriture: |
---|
546 | ! |
---|
547 | ! AVEC xios, on commence a remplir les fichiers de sortie a partir du DEUXIEME |
---|
548 | ! appel de cette interface (lorsque cosp_init_flag = 1). |
---|
549 | ! |
---|
550 | ! SANS xios, on commence a remplir les fichiers de sortie a partir du PREMIER |
---|
551 | ! appel de cette interface (lorsque cosp_init_flag = 1). |
---|
552 | ! |
---|
553 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
554 | |
---|
555 | print *, 'Calling write output' |
---|
556 | call lmdz_cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, & |
---|
557 | missing_val, cfg, niv_sorties, cospOUT) |
---|
558 | |
---|
559 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
560 | ! |
---|
561 | ! 8) On libere la memoire allouee lors de cet appel a l'interface |
---|
562 | ! |
---|
563 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
564 | |
---|
565 | call destroy_cospIN(cospIN) |
---|
566 | call destroy_cospstateIN(cospstateIN) |
---|
567 | call destroy_cosp_outputs(cospOUT) |
---|
568 | |
---|
569 | endif ! cosp_init_flag = 1 |
---|
570 | |
---|
571 | end subroutine lmdz_cosp_interface |
---|