LMDZ
phys_state_var_mod.F90
Go to the documentation of this file.
1 !
2 ! $Id: phys_state_var_mod.F90 2366 2015-09-21 20:41:04Z oboucher $
3 !
4  MODULE phys_state_var_mod
5 ! Variables sauvegardees pour le startphy.nc
6 !======================================================================
7 !
8 !
9 !======================================================================
10 ! Declaration des variables
11  USE dimphy
12  USE netcdf, only: nf90_fill_real
13  INTEGER, PARAMETER :: nlevstd=17
14  INTEGER, PARAMETER :: nlevstd8=8
15  INTEGER, PARAMETER :: nlevstd3=3
16  INTEGER, PARAMETER :: nout=3
17  INTEGER, PARAMETER :: napisccp=1
18  INTEGER, SAVE :: radpas
19  REAL, PARAMETER :: missing_val_nf90=nf90_fill_real
20 !$OMP THREADPRIVATE(radpas)
21  REAL, SAVE :: dtime, solaire_etat0
22 !$OMP THREADPRIVATE(dtime, solaire_etat0)
23 
24  REAL, ALLOCATABLE, SAVE :: rlat(:), rlon(:), pctsrf(:,:)
25 !$OMP THREADPRIVATE(rlat, rlon, pctsrf)
26  REAL, ALLOCATABLE, SAVE :: ftsol(:,:)
27 !$OMP THREADPRIVATE(ftsol)
28  REAL,ALLOCATABLE,SAVE :: qsol(:),fevap(:,:),z0m(:,:),z0h(:,:),agesno(:,:)
29 !$OMP THREADPRIVATE(qsol,fevap,z0m,z0h,agesno)
30 ! character(len=6), SAVE :: ocean
31 !!!!!!$OMP THREADPRIVATE(ocean)
32 ! logical, SAVE :: ok_veget
33 !!!!!!$OMP THREADPRIVATE(ok_veget)
34  REAL, ALLOCATABLE, SAVE :: falb1(:,:), falb2(:,:)
35 !$OMP THREADPRIVATE(falb1, falb2)
36 
37 !albedo SB >>>
38  REAL, ALLOCATABLE, SAVE :: falb_dif(:,:,:), falb_dir(:,:,:)
39  real, allocatable, save :: chl_con(:)
40 !$OMP THREADPRIVATE(falb_dir,falb_dif,chl_con)
41 !albedo SB <<<
42 
43 
44  REAL, ALLOCATABLE, SAVE :: rain_fall(:), snow_fall(:)
45 !$OMP THREADPRIVATE( rain_fall, snow_fall)
46  REAL, ALLOCATABLE, SAVE :: solsw(:), sollw(:)
47 !$OMP THREADPRIVATE(solsw, sollw)
48  REAL, ALLOCATABLE, SAVE :: radsol(:)
49 !$OMP THREADPRIVATE(radsol)
50  REAL, ALLOCATABLE, SAVE :: swradcorr(:)
51 !$OMP THREADPRIVATE(swradcorr)
52 
53 !clesphy0 param physiq
54 !
55 ! Parametres de l'Orographie a l'Echelle Sous-Maille (OESM):
56 !
57  REAL, ALLOCATABLE, SAVE :: zmea(:), zstd(:), zsig(:), zgam(:)
58 !$OMP THREADPRIVATE(zmea, zstd, zsig, zgam)
59  REAL, ALLOCATABLE, SAVE :: zthe(:), zpic(:), zval(:)
60 !$OMP THREADPRIVATE(zthe, zpic, zval)
61 ! REAL tabcntr0(100)
62  REAL, ALLOCATABLE, SAVE :: rugoro(:)
63 !$OMP THREADPRIVATE(rugoro)
64  REAL, ALLOCATABLE, SAVE :: t_ancien(:,:), q_ancien(:,:)
65 !$OMP THREADPRIVATE(t_ancien, q_ancien)
66  REAL, ALLOCATABLE, SAVE :: u_ancien(:,:), v_ancien(:,:)
67 !$OMP THREADPRIVATE(u_ancien, v_ancien)
68 !!! RomP >>>
69  REAL, ALLOCATABLE, SAVE :: tr_ancien(:,:,:)
70 !$OMP THREADPRIVATE(tr_ancien)
71 !!! RomP <<<
72  LOGICAL, SAVE :: ancien_ok
73 !$OMP THREADPRIVATE(ancien_ok)
74  REAL, ALLOCATABLE, SAVE :: clwcon(:,:),rnebcon(:,:)
75 !$OMP THREADPRIVATE(clwcon,rnebcon)
76  REAL, ALLOCATABLE, SAVE :: qtc_cv(:,:),sigt_cv(:,:)
77 !$OMP THREADPRIVATE(qtc_cv,sigt_cv)
78  REAL, ALLOCATABLE, SAVE :: ratqs(:,:)
79 !$OMP THREADPRIVATE(ratqs)
80  REAL, ALLOCATABLE, SAVE :: pbl_tke(:,:,:) ! turb kinetic energy
81  REAL, ALLOCATABLE, SAVE :: coefh(:,:,:) ! Kz enthalpie
82  REAL, ALLOCATABLE, SAVE :: coefm(:,:,:) ! Kz momentum
83 !$OMP THREADPRIVATE(pbl_tke, coefh,coefm)
84 !nrlmd<
85  REAL, ALLOCATABLE, SAVE :: delta_tsurf(:,:) ! Surface temperature difference inside-outside cold pool
86 !$OMP THREADPRIVATE(delta_tsurf)
88  REAL, ALLOCATABLE, SAVE :: zmax0(:), f0(:) !
89 !$OMP THREADPRIVATE(zmax0,f0)
90  REAL, ALLOCATABLE, SAVE :: sig1(:,:), w01(:,:)
91 !$OMP THREADPRIVATE(sig1,w01)
92  REAL, ALLOCATABLE, SAVE :: entr_therm(:,:), fm_therm(:,:)
93 !$OMP THREADPRIVATE(entr_therm,fm_therm)
94  REAL, ALLOCATABLE, SAVE :: detr_therm(:,:)
95 !$OMP THREADPRIVATE(detr_therm)
96 !IM 150408
97 ! pour phsystoke avec thermiques
98  REAL,ALLOCATABLE,SAVE :: clwcon0th(:,:),rnebcon0th(:,:)
99 !$OMP THREADPRIVATE(clwcon0th,rnebcon0th)
100 ! radiation outputs
101  REAL,ALLOCATABLE,SAVE :: swdn0(:,:), swdn(:,:)
102 !$OMP THREADPRIVATE(swdn0,swdn)
103  REAL,ALLOCATABLE,SAVE :: swup0(:,:), swup(:,:)
104 !$OMP THREADPRIVATE(swup0,swup)
105  REAL,ALLOCATABLE,SAVE :: swdn200clr(:), swdn200(:)
106 !$OMP THREADPRIVATE(SWdn200clr,SWdn200)
107  REAL,ALLOCATABLE,SAVE :: swup200clr(:), swup200(:)
108 !$OMP THREADPRIVATE(SWup200clr,SWup200)
109  REAL,ALLOCATABLE,SAVE :: lwdn0(:,:), lwdn(:,:)
110 !$OMP THREADPRIVATE(lwdn0,lwdn)
111  REAL,ALLOCATABLE,SAVE :: lwup0(:,:), lwup(:,:)
112 !$OMP THREADPRIVATE(lwup0,lwup)
113  REAL,ALLOCATABLE,SAVE :: lwdn200clr(:), lwdn200(:)
114 !$OMP THREADPRIVATE(LWdn200clr,LWdn200)
115  REAL,ALLOCATABLE,SAVE :: lwup200clr(:), lwup200(:)
116 !$OMP THREADPRIVATE(LWup200clr,LWup200)
117  REAL,ALLOCATABLE,SAVE :: lwdntoa(:), lwdntoaclr(:)
118 !$OMP THREADPRIVATE(LWdnTOA,LWdnTOAclr)
119 ! pressure level
120  REAL,ALLOCATABLE,SAVE :: tsumstd(:,:,:)
121 !$OMP THREADPRIVATE(tsumSTD)
122  REAL,ALLOCATABLE,SAVE :: usumstd(:,:,:), vsumstd(:,:,:)
123 !$OMP THREADPRIVATE(usumSTD,vsumSTD)
124  REAL,ALLOCATABLE,SAVE :: wsumstd(:,:,:), phisumstd(:,:,:)
125 !$OMP THREADPRIVATE(wsumSTD,phisumSTD)
126  REAL,ALLOCATABLE,SAVE :: qsumstd(:,:,:), rhsumstd(:,:,:)
127 !$OMP THREADPRIVATE(qsumSTD,rhsumSTD)
128  REAL,ALLOCATABLE,SAVE :: tnondef(:,:,:)
129 !$OMP THREADPRIVATE(tnondef)
130  REAL,ALLOCATABLE,SAVE :: uvsumstd(:,:,:)
131 !$OMP THREADPRIVATE(uvsumSTD)
132  REAL,ALLOCATABLE,SAVE :: vqsumstd(:,:,:)
133 !$OMP THREADPRIVATE(vqsumSTD)
134  REAL,ALLOCATABLE,SAVE :: vtsumstd(:,:,:)
135 !$OMP THREADPRIVATE(vTsumSTD)
136  REAL,ALLOCATABLE,SAVE :: wqsumstd(:,:,:)
137 !$OMP THREADPRIVATE(wqsumSTD)
138  REAL,ALLOCATABLE,SAVE :: vphisumstd(:,:,:)
139 !$OMP THREADPRIVATE(vphisumSTD)
140  REAL,ALLOCATABLE,SAVE :: wtsumstd(:,:,:)
141 !$OMP THREADPRIVATE(wTsumSTD)
142  REAL,ALLOCATABLE,SAVE :: u2sumstd(:,:,:)
143 !$OMP THREADPRIVATE(u2sumSTD)
144  REAL,ALLOCATABLE,SAVE :: v2sumstd(:,:,:)
145 !$OMP THREADPRIVATE(v2sumSTD)
146  REAL,ALLOCATABLE,SAVE :: t2sumstd(:,:,:)
147 !$OMP THREADPRIVATE(T2sumSTD)
148  REAL,ALLOCATABLE,SAVE :: o3sumstd(:,:,:), o3daysumstd(:,:,:)
149 !$OMP THREADPRIVATE(O3sumSTD,O3daysumSTD)
150 !IM begin
151  REAL,ALLOCATABLE,SAVE :: wlevstd(:,:), ulevstd(:,:), vlevstd(:,:)
152 !$OMP THREADPRIVATE(wlevSTD,ulevSTD,vlevSTD)
153  REAL,ALLOCATABLE,SAVE :: tlevstd(:,:), qlevstd(:,:), rhlevstd(:,:)
154 !$OMP THREADPRIVATE(tlevSTD,qlevSTD,rhlevSTD)
155  REAL,ALLOCATABLE,SAVE :: philevstd(:,:)
156 !$OMP THREADPRIVATE(philevSTD)
157  REAL,ALLOCATABLE,SAVE :: uvstd(:,:)
158 !$OMP THREADPRIVATE(uvSTD)
159  REAL,ALLOCATABLE,SAVE :: vqstd(:,:)
160 !$OMP THREADPRIVATE(vqSTD)
161  REAL,ALLOCATABLE,SAVE :: vtstd(:,:)
162 !$OMP THREADPRIVATE(vTSTD)
163  REAL,ALLOCATABLE,SAVE :: wqstd(:,:)
164 !$OMP THREADPRIVATE(wqSTD)
165  REAL,ALLOCATABLE,SAVE :: vphistd(:,:)
166 !$OMP THREADPRIVATE(vphiSTD)
167  REAL,ALLOCATABLE,SAVE :: wtstd(:,:)
168 !$OMP THREADPRIVATE(wTSTD)
169  REAL,ALLOCATABLE,SAVE :: u2std(:,:)
170 !$OMP THREADPRIVATE(u2STD)
171  REAL,ALLOCATABLE,SAVE :: v2std(:,:)
172 !$OMP THREADPRIVATE(v2STD)
173  REAL,ALLOCATABLE,SAVE :: t2std(:,:)
174 !$OMP THREADPRIVATE(T2STD)
175  REAL,ALLOCATABLE,SAVE :: o3std(:,:), o3daystd(:,:)
176 !$OMP THREADPRIVATE(O3STD,O3daySTD)
177 !IM end
178  INTEGER,ALLOCATABLE,SAVE :: seed_old(:,:)
179 !$OMP THREADPRIVATE(seed_old)
180  REAL,ALLOCATABLE,SAVE :: zuthe(:),zvthe(:)
181 !$OMP THREADPRIVATE(zuthe,zvthe)
182  REAL,ALLOCATABLE,SAVE :: alb_neig(:)
183 !$OMP THREADPRIVATE(alb_neig)
184 !cloud base mass flux
185  REAL,ALLOCATABLE,SAVE :: ema_cbmf(:)
186 !$OMP THREADPRIVATE(ema_cbmf)
187 !cloud base pressure & cloud top pressure
188  REAL,ALLOCATABLE,SAVE :: ema_pcb(:), ema_pct(:)
189 !$OMP THREADPRIVATE(ema_pcb,ema_pct)
190  REAL,ALLOCATABLE,SAVE :: ma(:,:) ! undilute upward mass flux
191 !$OMP THREADPRIVATE(Ma)
192  REAL,ALLOCATABLE,SAVE :: qcondc(:,:) ! in-cld water content from convect
193 !$OMP THREADPRIVATE(qcondc)
194  REAL,ALLOCATABLE,SAVE :: wd(:) ! sb
195 !$OMP THREADPRIVATE(wd)
196  REAL,ALLOCATABLE,SAVE :: sigd(:)
197 !$OMP THREADPRIVATE(sigd)
198 !
199  REAL,ALLOCATABLE,SAVE :: cin(:)
200 !$OMP THREADPRIVATE(cin)
201 ! ftd : differential heating between wake and environment
202  REAL,ALLOCATABLE,SAVE :: ftd(:,:)
203 !$OMP THREADPRIVATE(ftd)
204 ! fqd : differential moistening between wake and environment
205  REAL,ALLOCATABLE,SAVE :: fqd(:,:)
206 !$OMP THREADPRIVATE(fqd)
207 !34EK
208 ! -- Variables de controle de ALE et ALP
209 !ALE : Energie disponible pour soulevement : utilisee par la
210 ! convection d'Emanuel pour le declenchement et la regulation
211  REAL,ALLOCATABLE,SAVE :: ale(:)
212 !$OMP THREADPRIVATE(ALE)
213 !ALP : Puissance disponible pour soulevement
214  REAL,ALLOCATABLE,SAVE :: alp(:)
215 !$OMP THREADPRIVATE(ALP)
216 !
217 ! nouvelles variables pour le couplage convection-couche limite
218  REAL,ALLOCATABLE,SAVE :: ale_bl(:)
219 !$OMP THREADPRIVATE(Ale_bl)
220  REAL,ALLOCATABLE,SAVE :: alp_bl(:)
221 !$OMP THREADPRIVATE(Alp_bl)
222  INTEGER,ALLOCATABLE,SAVE :: lalim_conv(:)
223 !$OMP THREADPRIVATE(lalim_conv)
224  REAL,ALLOCATABLE,SAVE :: wght_th(:,:)
225 !$OMP THREADPRIVATE(wght_th)
226 !
227 ! variables de la wake
228 ! wake_deltat : ecart de temperature avec la zone non perturbee
229 ! wake_deltaq : ecart d'humidite avec la zone non perturbee
230 ! wake_Cstar : vitesse d'etalement de la poche
231 ! wake_s : fraction surfacique occupee par la poche froide
232 ! wake_pe : wake potential energy - WAPE
233 ! wake_fip : Gust Front Impinging power - ALP
234 ! dt_wake, dq_wake: LS tendencies due to wake
235  REAL,ALLOCATABLE,SAVE :: wake_deltat(:,:)
236 !$OMP THREADPRIVATE(wake_deltat)
237  REAL,ALLOCATABLE,SAVE :: wake_deltaq(:,:)
238 !$OMP THREADPRIVATE(wake_deltaq)
239  REAL,ALLOCATABLE,SAVE :: wake_cstar(:)
240 !$OMP THREADPRIVATE(wake_Cstar)
241  REAL,ALLOCATABLE,SAVE :: wake_s(:)
242 !$OMP THREADPRIVATE(wake_s)
243  REAL,ALLOCATABLE,SAVE :: wake_pe(:)
244 !$OMP THREADPRIVATE(wake_pe)
245  REAL,ALLOCATABLE,SAVE :: wake_fip(:)
246 !$OMP THREADPRIVATE(wake_fip)
247  REAL,ALLOCATABLE,SAVE :: dt_wake(:,:)
248 !$OMP THREADPRIVATE(dt_wake)
249  REAL,ALLOCATABLE,SAVE :: dq_wake(:,:)
250 !$OMP THREADPRIVATE(dq_wake)
251 !
252 !jyg<
253 ! variables related to the spitting of the PBL between wake and
254 ! off-wake regions.
255 ! wake_delta_pbl_TKE : difference TKE_w - TKE_x
256  REAL,ALLOCATABLE,SAVE :: wake_delta_pbl_tke(:,:,:)
257 !$OMP THREADPRIVATE(wake_delta_pbl_TKE)
259 !
260 ! pfrac_impa : Produits des coefs lessivage impaction
261 ! pfrac_nucl : Produits des coefs lessivage nucleation
262 ! pfrac_1nucl: Produits des coefs lessi nucl (alpha = 1)
263  REAL,ALLOCATABLE,SAVE :: pfrac_impa(:,:), pfrac_nucl(:,:)
264 !$OMP THREADPRIVATE(pfrac_impa,pfrac_nucl)
265  REAL,ALLOCATABLE,SAVE :: pfrac_1nucl(:,:)
266 !$OMP THREADPRIVATE(pfrac_1nucl)
267 !
268  REAL,ALLOCATABLE,SAVE :: total_rain(:), nday_rain(:)
269 !$OMP THREADPRIVATE(total_rain,nday_rain)
270  REAL,ALLOCATABLE,SAVE :: paire_ter(:)
271 !$OMP THREADPRIVATE(paire_ter)
272 ! albsol1: albedo du sol total pour SW visible
273 ! albsol2: albedo du sol total pour SW proche IR
274  REAL,ALLOCATABLE,SAVE :: albsol1(:), albsol2(:)
275 !$OMP THREADPRIVATE(albsol1,albsol2)
276 
277 !albedo SB >>>
278  REAL,ALLOCATABLE,SAVE :: albsol_dif(:,:),albsol_dir(:,:)
279 !$OMP THREADPRIVATE(albsol_dif,albsol_dir)
280 !albedo SB <<<
281 
282 
283  REAL, ALLOCATABLE, SAVE:: wo(:, :, :)
284  ! column-density of ozone in a layer, in kilo-Dobsons
285  ! Third dimension has size 1 or 2.
286  ! "wo(:, :, 1)" is for the average day-night field,
287  ! "wo(:, :, 2)" is for daylight time.
288  !$OMP THREADPRIVATE(wo)
289 
290 ! heat : chauffage solaire
291 ! heat0: chauffage solaire ciel clair
292 ! cool : refroidissement infrarouge
293 ! cool0 : refroidissement infrarouge ciel clair
294 ! sollwdown : downward LW flux at surface
295 ! sollwdownclr : downward CS LW flux at surface
296 ! toplwdown : downward CS LW flux at TOA
297 ! toplwdownclr : downward CS LW flux at TOA
298  REAL,ALLOCATABLE,SAVE :: clwcon0(:,:),rnebcon0(:,:)
299 !$OMP THREADPRIVATE(clwcon0,rnebcon0)
300  REAL,ALLOCATABLE,SAVE :: heat(:,:)
301 !$OMP THREADPRIVATE(heat)
302  REAL,ALLOCATABLE,SAVE :: heat0(:,:)
303 !$OMP THREADPRIVATE(heat0)
304  REAL,ALLOCATABLE,SAVE :: cool(:,:)
305 !$OMP THREADPRIVATE(cool)
306  REAL,ALLOCATABLE,SAVE :: cool0(:,:)
307 !$OMP THREADPRIVATE(cool0)
308  REAL,ALLOCATABLE,SAVE :: topsw(:), toplw(:)
309 !$OMP THREADPRIVATE(topsw,toplw)
310  REAL,ALLOCATABLE,SAVE :: sollwdown(:)
311 !$OMP THREADPRIVATE(sollwdown)
312  REAL,ALLOCATABLE,SAVE :: gustiness(:)
313 !$OMP THREADPRIVATE(gustiness)
314  REAL,ALLOCATABLE,SAVE :: sollwdownclr(:)
315 !$OMP THREADPRIVATE(sollwdownclr)
316  REAL,ALLOCATABLE,SAVE :: toplwdown(:)
317 !$OMP THREADPRIVATE(toplwdown)
318  REAL,ALLOCATABLE,SAVE :: toplwdownclr(:)
319 !$OMP THREADPRIVATE(toplwdownclr)
320  REAL,ALLOCATABLE,SAVE :: topsw0(:),toplw0(:),solsw0(:),sollw0(:)
321 !$OMP THREADPRIVATE(topsw0,toplw0,solsw0,sollw0)
322  REAL,ALLOCATABLE,SAVE :: albpla(:)
323 !$OMP THREADPRIVATE(albpla)
324 
325 !IM ajout variables CFMIP2/CMIP5
326  REAL,ALLOCATABLE,SAVE :: heatp(:,:), coolp(:,:)
327 !$OMP THREADPRIVATE(heatp, coolp)
328  REAL,ALLOCATABLE,SAVE :: heat0p(:,:), cool0p(:,:)
329 !$OMP THREADPRIVATE(heat0p, cool0p)
330  REAL,ALLOCATABLE,SAVE :: radsolp(:), topswp(:), toplwp(:)
331 !$OMP THREADPRIVATE(radsolp, topswp, toplwp)
332  REAL,ALLOCATABLE,SAVE :: albplap(:)
333 !$OMP THREADPRIVATE(albplap)
334  REAL,ALLOCATABLE,SAVE :: solswp(:), sollwp(:)
335 !$OMP THREADPRIVATE(solswp, sollwp)
336  REAL,ALLOCATABLE,SAVE :: sollwdownp(:)
337 !$OMP THREADPRIVATE(sollwdownp)
338  REAL,ALLOCATABLE,SAVE :: topsw0p(:),toplw0p(:)
339  REAL,ALLOCATABLE,SAVE :: solsw0p(:),sollw0p(:)
340 !$OMP THREADPRIVATE(topsw0p,toplw0p,solsw0p,sollw0p)
341  REAL,ALLOCATABLE,SAVE :: lwdn0p(:,:), lwdnp(:,:)
342  REAL,ALLOCATABLE,SAVE :: lwup0p(:,:), lwupp(:,:)
343 !$OMP THREADPRIVATE(lwdn0p, lwdnp, lwup0p, lwupp)
344  REAL,ALLOCATABLE,SAVE :: swdn0p(:,:), swdnp(:,:)
345  REAL,ALLOCATABLE,SAVE :: swup0p(:,:), swupp(:,:)
346 !$OMP THREADPRIVATE(swdn0p, swdnp, swup0p, swupp)
347 
348 ! pbase : cloud base pressure
349 ! bbase : cloud base buoyancy
350  REAL,ALLOCATABLE,SAVE :: cape(:)
351 !$OMP THREADPRIVATE(cape)
352  REAL,ALLOCATABLE,SAVE :: pbase(:)
353 !$OMP THREADPRIVATE(pbase)
354  REAL,ALLOCATABLE,SAVE :: bbase(:)
355 !$OMP THREADPRIVATE(bbase)
356 !
357  REAL,SAVE,ALLOCATABLE :: zqasc(:,:)
358 !$OMP THREADPRIVATE( zqasc)
359  INTEGER,ALLOCATABLE,SAVE :: ibas_con(:), itop_con(:)
360 !$OMP THREADPRIVATE(ibas_con,itop_con)
361  REAL,SAVE,ALLOCATABLE :: rain_con(:)
362 !$OMP THREADPRIVATE(rain_con)
363  REAL,SAVE,ALLOCATABLE :: snow_con(:)
364 !$OMP THREADPRIVATE(snow_con)
365 !
366  REAL,SAVE,ALLOCATABLE :: rlonpos(:)
367 !$OMP THREADPRIVATE(rlonPOS)
368  REAL,SAVE,ALLOCATABLE :: newsst(:)
369 !$OMP THREADPRIVATE(newsst)
370  REAL,SAVE,ALLOCATABLE :: ustar(:,:),u10m(:,:), v10m(:,:),wstar(:,:)
371 !$OMP THREADPRIVATE(ustar,u10m,v10m,wstar)
372 !
373 ! ok_ade=T -ADE=topswad-topsw
374 ! ok_aie=T ->
375 ! ok_ade=T -AIE=topswai-topswad
376 ! ok_ade=F -AIE=topswai-topsw
377 !
378 !topswad, solswad : Aerosol direct effect
379  REAL,SAVE,ALLOCATABLE :: topswad(:), solswad(:)
380 !$OMP THREADPRIVATE(topswad,solswad)
381 !topswai, solswai : Aerosol indirect effect
382  REAL,SAVE,ALLOCATABLE :: topswai(:), solswai(:)
383 !$OMP THREADPRIVATE(topswai,solswai)
384 
385  REAL,SAVE,ALLOCATABLE :: tau_aero(:,:,:,:), piz_aero(:,:,:,:), cg_aero(:,:,:,:)
386 !$OMP THREADPRIVATE(tau_aero, piz_aero, cg_aero)
387  REAL,SAVE,ALLOCATABLE :: tau_aero_sw_rrtm(:,:,:,:), piz_aero_sw_rrtm(:,:,:,:), cg_aero_sw_rrtm(:,:,:,:)
388 !$OMP THREADPRIVATE(tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm)
389  REAL,SAVE,ALLOCATABLE :: tau_aero_lw_rrtm(:,:,:,:), piz_aero_lw_rrtm(:,:,:,:), cg_aero_lw_rrtm(:,:,:,:)
390 !$OMP THREADPRIVATE(tau_aero_lw_rrtm, piz_aero_lw_rrtm, cg_aero_lw_rrtm)
391  REAL,SAVE,ALLOCATABLE :: ccm(:,:,:)
392 !$OMP THREADPRIVATE(ccm)
393 
394 !!! nrlmd le 10/04/2012
395  REAL,SAVE,ALLOCATABLE :: ale_bl_trig(:)
396 !$OMP THREADPRIVATE(ale_bl_trig)
397 !!! fin nrlmd le 10/04/2012
398 
399  REAL, ALLOCATABLE, SAVE:: du_gwd_rando(:, :), du_gwd_front(:, :)
400  !$OMP THREADPRIVATE(du_gwd_rando, du_gwd_front)
401  ! tendencies on wind due to gravity waves
402 
403 CONTAINS
404 
405 !======================================================================
406 SUBROUTINE phys_state_var_init(read_climoz)
408 USE aero_mod
409 USE infotrac_phy, ONLY : nbtr
410 USE indice_sol_mod
411 IMPLICIT NONE
412 
413 integer, intent(in):: read_climoz
414 ! read ozone climatology
415 ! Allowed values are 0, 1 and 2
416 ! 0: do not read an ozone climatology
417 ! 1: read a single ozone climatology that will be used day and night
418 ! 2: read two ozone climatologies, the average day and night
419 ! climatology and the daylight climatology
420 
421 include "clesphys.h"
422  ALLOCATE(rlat(klon), rlon(klon))
423  ALLOCATE(pctsrf(klon,nbsrf))
424  ALLOCATE(ftsol(klon,nbsrf))
425  ALLOCATE(qsol(klon),fevap(klon,nbsrf))
426  ALLOCATE(z0m(klon,nbsrf+1),z0h(klon,nbsrf+1),agesno(klon,nbsrf))
427  ALLOCATE(falb1(klon,nbsrf))
428  ALLOCATE(falb2(klon,nbsrf))
429 !albedo SB >>>
430  ALLOCATE(falb_dir(klon,nsw,nbsrf),falb_dif(klon,nsw,nbsrf))
431  ALLOCATE(chl_con(klon))
432 !albedo SB <<<
433  ALLOCATE(rain_fall(klon))
434  ALLOCATE(snow_fall(klon))
435  ALLOCATE(solsw(klon), sollw(klon))
436  ALLOCATE(radsol(klon))
437  ALLOCATE(swradcorr(klon))
438  ALLOCATE(zmea(klon), zstd(klon), zsig(klon), zgam(klon))
439  ALLOCATE(zthe(klon), zpic(klon), zval(klon))
440 
441  ALLOCATE(rugoro(klon))
442  ALLOCATE(t_ancien(klon,klev), q_ancien(klon,klev))
443  ALLOCATE(u_ancien(klon,klev), v_ancien(klon,klev))
444 !!! Rom P >>>
445  ALLOCATE(tr_ancien(klon,klev,nbtr))
446 !!! Rom P <<<
447  ALLOCATE(clwcon(klon,klev),rnebcon(klon,klev))
448  ALLOCATE(qtc_cv(klon,klev),sigt_cv(klon,klev))
449  ALLOCATE(ratqs(klon,klev))
450  ALLOCATE(pbl_tke(klon,klev+1,nbsrf+1))
451 !nrlmd<
452  ALLOCATE(delta_tsurf(klon,nbsrf))
454  ALLOCATE(coefh(klon,klev+1,nbsrf+1))
455  ALLOCATE(coefm(klon,klev+1,nbsrf+1))
456  ALLOCATE(zmax0(klon), f0(klon))
457  ALLOCATE(sig1(klon,klev), w01(klon,klev))
458  ALLOCATE(entr_therm(klon,klev), fm_therm(klon,klev+1))
459  ALLOCATE(detr_therm(klon,klev))
460 ! pour phsystoke avec thermiques
461  ALLOCATE(clwcon0th(klon,klev),rnebcon0th(klon,klev))
462 ! radiation outputs
463  ALLOCATE(swdn0(klon,klevp1), swdn(klon,klevp1))
464  ALLOCATE(swup0(klon,klevp1), swup(klon,klevp1))
465  ALLOCATE(lwdn0(klon,klevp1), lwdn(klon,klevp1))
466  ALLOCATE(lwup0(klon,klevp1), lwup(klon,klevp1))
467  ALLOCATE(swdn200clr(klon), swdn200(klon))
468  ALLOCATE(swup200clr(klon), swup200(klon))
469  ALLOCATE(lwdn200clr(klon), lwdn200(klon))
470  ALLOCATE(lwup200clr(klon), lwup200(klon))
471  ALLOCATE(lwdntoa(klon), lwdntoaclr(klon))
472 ! pressure level
473  ALLOCATE(tsumstd(klon,nlevstd,nout))
477  ALLOCATE(tnondef(klon,nlevstd,nout))
478  ALLOCATE(uvsumstd(klon,nlevstd,nout))
479  ALLOCATE(vqsumstd(klon,nlevstd,nout))
480  ALLOCATE(vtsumstd(klon,nlevstd,nout))
481  ALLOCATE(wqsumstd(klon,nlevstd,nout))
482  ALLOCATE(vphisumstd(klon,nlevstd,nout))
483  ALLOCATE(wtsumstd(klon,nlevstd,nout))
484  ALLOCATE(u2sumstd(klon,nlevstd,nout))
485  ALLOCATE(v2sumstd(klon,nlevstd,nout))
486  ALLOCATE(t2sumstd(klon,nlevstd,nout))
487  ALLOCATE(o3sumstd(klon,nlevstd,nout))
488  ALLOCATE(o3daysumstd(klon,nlevstd,nout))
489 !IM beg
492  ALLOCATE(philevstd(klon,nlevstd))
493  ALLOCATE(uvstd(klon,nlevstd),vqstd(klon,nlevstd))
494  ALLOCATE(vtstd(klon,nlevstd),wqstd(klon,nlevstd))
495  ALLOCATE(vphistd(klon,nlevstd),wtstd(klon,nlevstd))
496  ALLOCATE(u2std(klon,nlevstd),v2std(klon,nlevstd))
497  ALLOCATE(t2std(klon,nlevstd))
498  ALLOCATE(o3std(klon,nlevstd))
499  ALLOCATE(o3daystd(klon,nlevstd))
500 !IM end
501  ALLOCATE(seed_old(klon,napisccp))
502  ALLOCATE(zuthe(klon),zvthe(klon))
503  ALLOCATE(alb_neig(klon))
504 !cloud base mass flux
505  ALLOCATE(ema_cbmf(klon))
506 !cloud base pressure & cloud top pressure
507  ALLOCATE(ema_pcb(klon), ema_pct(klon))
508 !
509  ALLOCATE(ma(klon,klev))
510  ALLOCATE(qcondc(klon,klev))
511  ALLOCATE(wd(klon))
512  ALLOCATE(sigd(klon))
513  ALLOCATE(cin(klon), ale(klon), alp(klon))
514  ALLOCATE(ftd(klon,klev), fqd(klon,klev))
515  ALLOCATE(ale_bl(klon))
516  ALLOCATE(alp_bl(klon))
517  ALLOCATE(lalim_conv(klon))
518  ALLOCATE(wght_th(klon,klev))
520  ALLOCATE(wake_cstar(klon), wake_s(klon))
521  ALLOCATE(wake_pe(klon), wake_fip(klon))
522  ALLOCATE(dt_wake(klon,klev), dq_wake(klon,klev))
523 !jyg<
524  ALLOCATE(wake_delta_pbl_tke(klon,klev+1,nbsrf+1))
526  ALLOCATE(pfrac_impa(klon,klev), pfrac_nucl(klon,klev))
527  ALLOCATE(pfrac_1nucl(klon,klev))
528  ALLOCATE(total_rain(klon), nday_rain(klon))
529  ALLOCATE(paire_ter(klon))
530  ALLOCATE(albsol1(klon), albsol2(klon))
531 !albedo SB >>>
532  ALLOCATE(albsol_dir(klon,nsw),albsol_dif(klon,nsw))
533 !albedo SB <<<
534 
535  if (read_climoz <= 1) then
536  ALLOCATE(wo(klon,klev, 1))
537  else
538  ! read_climoz == 2
539  ALLOCATE(wo(klon,klev, 2))
540  end if
541 
542  ALLOCATE(clwcon0(klon,klev),rnebcon0(klon,klev))
543  ALLOCATE(heat(klon,klev), heat0(klon,klev))
544  ALLOCATE(cool(klon,klev), cool0(klon,klev))
545  ALLOCATE(topsw(klon), toplw(klon))
546  ALLOCATE(sollwdown(klon), sollwdownclr(klon))
547  ALLOCATE(toplwdown(klon), toplwdownclr(klon))
548  ALLOCATE(topsw0(klon),toplw0(klon),solsw0(klon),sollw0(klon))
549  ALLOCATE(albpla(klon))
550 !IM ajout variables CFMIP2/CMIP5
551  ALLOCATE(heatp(klon,klev), coolp(klon,klev))
552  ALLOCATE(heat0p(klon,klev), cool0p(klon,klev))
553  ALLOCATE(radsolp(klon), topswp(klon), toplwp(klon))
554  ALLOCATE(albplap(klon))
555  ALLOCATE(solswp(klon), sollwp(klon))
556  ALLOCATE(gustiness(klon))
557  ALLOCATE(sollwdownp(klon))
558  ALLOCATE(topsw0p(klon),toplw0p(klon))
559  ALLOCATE(solsw0p(klon),sollw0p(klon))
560  ALLOCATE(lwdn0p(klon,klevp1), lwdnp(klon,klevp1))
561  ALLOCATE(lwup0p(klon,klevp1), lwupp(klon,klevp1))
562  ALLOCATE(swdn0p(klon,klevp1), swdnp(klon,klevp1))
563  ALLOCATE(swup0p(klon,klevp1), swupp(klon,klevp1))
564 
565  ALLOCATE(cape(klon))
566  ALLOCATE(pbase(klon),bbase(klon))
567  ALLOCATE(zqasc(klon,klev))
568  ALLOCATE(ibas_con(klon), itop_con(klon))
569  ALLOCATE(rain_con(klon), snow_con(klon))
570  ALLOCATE(rlonpos(klon))
571  ALLOCATE(newsst(klon))
573  ALLOCATE(topswad(klon), solswad(klon))
574  ALLOCATE(topswai(klon), solswai(klon))
580  ALLOCATE(ccm(klon,klev,nbands))
581 
582 !!! nrlmd le 10/04/2012
583  ALLOCATE(ale_bl_trig(klon))
584 !!! fin nrlmd le 10/04/2012
585  if (ok_gwd_rando) allocate(du_gwd_rando(klon, klev))
586  if (.not. ok_hines .and. ok_gwd_rando) allocate(du_gwd_front(klon, klev))
587 
588 END SUBROUTINE phys_state_var_init
589 
590 !======================================================================
591 SUBROUTINE phys_state_var_end
592 USE dimphy
593 USE indice_sol_mod
594 IMPLICIT NONE
595 include "clesphys.h"
596 
597  deallocate(rlat, rlon, pctsrf, ftsol, falb1, falb2)
598  deallocate(qsol,fevap,z0m,z0h,agesno)
599  deallocate(rain_fall, snow_fall, solsw, sollw, radsol, swradcorr)
600  deallocate(zmea, zstd, zsig, zgam)
601  deallocate(zthe, zpic, zval)
602  deallocate(rugoro, t_ancien, q_ancien, clwcon, rnebcon)
603  deallocate(qtc_cv,sigt_cv)
604  deallocate( u_ancien, v_ancien )
605  deallocate( tr_ancien) !RomP
606  deallocate(ratqs, pbl_tke,coefh,coefm)
607 !nrlmd<
608  deallocate(delta_tsurf)
610  deallocate(zmax0, f0)
611  deallocate(sig1, w01)
612  deallocate(entr_therm, fm_therm)
613  deallocate(detr_therm)
614  deallocate(clwcon0th, rnebcon0th)
615 ! radiation outputs
616  deallocate(swdn0, swdn)
617  deallocate(swup0, swup)
618  deallocate(lwdn0, lwdn)
619  deallocate(lwup0, lwup)
620  deallocate(swdn200clr, swdn200)
621  deallocate(swup200clr, swup200)
622  deallocate(lwdn200clr, lwdn200)
623  deallocate(lwup200clr, lwup200)
624  deallocate(lwdntoa, lwdntoaclr)
625 ! pressure level
626  deallocate(tsumstd)
627  deallocate(usumstd, vsumstd)
628  deallocate(wsumstd, phisumstd)
629  deallocate(tnondef)
630  deallocate(qsumstd, rhsumstd)
631  deallocate(uvsumstd)
632  deallocate(vqsumstd)
633  deallocate(vtsumstd)
634  deallocate(wqsumstd)
635  deallocate(vphisumstd)
636  deallocate(wtsumstd)
637  deallocate(u2sumstd)
638  deallocate(v2sumstd)
639  deallocate(t2sumstd)
640  deallocate(o3sumstd)
641  deallocate(o3daysumstd)
642 !IM beg
645 !IM end
646  deallocate(seed_old)
647  deallocate(zuthe, zvthe)
648  deallocate(alb_neig)
649  deallocate(ema_cbmf)
650  deallocate(ema_pcb, ema_pct)
651  deallocate(ma, qcondc)
652  deallocate(wd, sigd)
653  deallocate(cin, ale, alp)
654  deallocate(ftd, fqd)
655  deallocate(ale_bl, alp_bl)
656  deallocate(lalim_conv, wght_th)
657  deallocate(wake_deltat, wake_deltaq)
658  deallocate(wake_cstar, wake_s, wake_pe, wake_fip)
659  deallocate(dt_wake, dq_wake)
660 !jyg<
661  deallocate(wake_delta_pbl_tke)
663  deallocate(pfrac_impa, pfrac_nucl)
664  deallocate(pfrac_1nucl)
665  deallocate(total_rain, nday_rain)
666  deallocate(paire_ter)
667  deallocate(albsol1, albsol2)
668 !albedo SB >>>
670 !albedo SB <<<
671  deallocate(wo)
672  deallocate(clwcon0,rnebcon0)
673  deallocate(heat, heat0)
674  deallocate(cool, cool0)
675  deallocate(topsw, toplw)
676  deallocate(sollwdown, sollwdownclr)
677  deallocate(gustiness)
678  deallocate(toplwdown, toplwdownclr)
679  deallocate(topsw0,toplw0,solsw0,sollw0)
680  deallocate(albpla)
681 !IM ajout variables CFMIP2/CMIP5
682  deallocate(heatp, coolp)
683  deallocate(heat0p, cool0p)
684  deallocate(radsolp, topswp, toplwp)
685  deallocate(albplap)
686  deallocate(solswp, sollwp)
687  deallocate(sollwdownp)
688  deallocate(topsw0p,toplw0p)
689  deallocate(solsw0p,sollw0p)
690  deallocate(lwdn0p, lwdnp)
691  deallocate(lwup0p, lwupp)
692  deallocate(swdn0p, swdnp)
693  deallocate(swup0p, swupp)
694  deallocate(cape)
695  deallocate(pbase,bbase)
696  deallocate(zqasc)
697  deallocate(ibas_con, itop_con)
698  deallocate(rain_con, snow_con)
699  deallocate(rlonpos)
700  deallocate(newsst)
701  deallocate(ustar,u10m, v10m,wstar)
702  deallocate(topswad, solswad)
703  deallocate(topswai, solswai)
704  deallocate(tau_aero,piz_aero,cg_aero)
707  deallocate(ccm)
708  if (ok_gwd_rando) deallocate(du_gwd_rando)
709  if (.not. ok_hines .and. ok_gwd_rando) deallocate(du_gwd_front)
710 
711 !!! nrlmd le 10/04/2012
712  deallocate(ale_bl_trig)
713 !!! fin nrlmd le 10/04/2012
714 
715 END SUBROUTINE phys_state_var_end
716 
717  END MODULE phys_state_var_mod
real, dimension(:,:), allocatable, save tlevstd
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL &zphi geo500!IM on interpole a chaque pas de temps le & swdn0
real, dimension(:,:,:), allocatable, save v2sumstd
real, dimension(:,:), allocatable, save q_ancien
real, dimension(:), allocatable, save sollwp
real, dimension(:), allocatable, save ema_pcb
real, dimension(:,:), allocatable, save vtstd
real, dimension(:), allocatable, save zuthe
real, dimension(:,:), allocatable, save w01
integer, parameter napisccp
real, dimension(:), allocatable, save sollwdownclr
real, dimension(:,:), allocatable, save clwcon
real, dimension(:), allocatable, save toplwdownclr
real, dimension(:), allocatable, save total_rain
real, dimension(:), allocatable, save topsw
real, dimension(:,:), allocatable, save du_gwd_front
real, dimension(:,:), allocatable, save wtstd
real, dimension(:,:), allocatable, save albsol_dif
integer, parameter nbands
Definition: aero_mod.F90:94
real, dimension(:), allocatable, save f0
real, dimension(:,:), allocatable, save heat0
integer, save nbtr
real, dimension(:,:), allocatable, save qcondc
real, dimension(:), allocatable, save zval
real, dimension(:), allocatable, save zsig
real, dimension(:), allocatable, save snow_fall
real, dimension(:,:,:,:), allocatable, save piz_aero_sw_rrtm
real, dimension(:), allocatable, save lwdn200clr
real, dimension(:,:,:), allocatable, save falb_dir
real, dimension(:,:), allocatable, save wake_deltaq
real, dimension(:,:), allocatable, save heat
real, dimension(:,:,:), allocatable, save vsumstd
real, dimension(:,:), allocatable, save rnebcon0
integer, dimension(:), allocatable, save ibas_con
real, dimension(:), allocatable, save nday_rain
real, dimension(:,:,:), allocatable, save phisumstd
real, dimension(:), allocatable, save lwdntoa
real, dimension(:,:), allocatable, save uvstd
real, dimension(:,:), allocatable, save lwup0p
real, dimension(:,:), allocatable, save falb1
real, dimension(:,:), allocatable, save vphistd
real, dimension(:), allocatable, save rain_fall
real, dimension(:,:), allocatable, save sig1
real, dimension(:,:,:), allocatable, save o3sumstd
real, dimension(:,:,:,:), allocatable, save piz_aero_lw_rrtm
real, dimension(:,:), allocatable, save swdn0p
real, dimension(:,:), allocatable, save wlevstd
real, dimension(:,:), allocatable, save t_ancien
real, dimension(:,:), allocatable, save ftd
!$Header!integer nvarmx dtime
Definition: gradsdef.h:20
real, dimension(:), allocatable, save bbase
real, dimension(:,:), allocatable, save dq_wake
real, dimension(:), allocatable, save solsw0
integer, save klon
Definition: dimphy.F90:3
real, dimension(:,:), allocatable, save dt_wake
real, dimension(:), allocatable, save rlonpos
real, parameter missing_val_nf90
real, dimension(:), allocatable, save zmea
real, dimension(:,:,:,:), allocatable, save tau_aero
real, dimension(:,:,:), allocatable, save u2sumstd
real, dimension(:,:), allocatable, save rnebcon0th
real, dimension(:,:), allocatable, save pfrac_impa
jyg
real, dimension(:,:), allocatable, save t2std
real, dimension(:), allocatable, save toplwdown
real, dimension(:,:), allocatable, save cool
real, dimension(:), allocatable, save pbase
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL &zphi geo500!IM on interpole a chaque pas de temps le SWdn200clr CALL SWup200clr CALL LWdn200clr CALL & lwup0
real, dimension(:,:), allocatable, save pctsrf
real, dimension(:,:), allocatable, save swup0p
real, dimension(:,:), allocatable, save falb2
real, dimension(:), allocatable, save radsol
real, dimension(:,:), allocatable, save entr_therm
integer, save klev
Definition: dimphy.F90:7
real, dimension(:), allocatable, save solsw0p
real, dimension(:), allocatable, save sollwdownp
real, dimension(:,:,:), allocatable, save ccm
real, dimension(:,:,:), allocatable, save vqsumstd
real, dimension(:,:,:,:), allocatable, save cg_aero
real, dimension(:), allocatable, save topswad
real, dimension(:), allocatable, save qsol
real, dimension(:,:), allocatable, save qlevstd
real, dimension(:,:), allocatable, save heatp
real, dimension(:,:), allocatable, save lwdnp
integer, dimension(:), allocatable, save itop_con
real, dimension(:,:,:), allocatable, save pbl_tke
real, dimension(:), allocatable, save sollw
real, dimension(:), allocatable, save cape
real, dimension(:,:,:,:), allocatable, save tau_aero_lw_rrtm
real, dimension(:), allocatable, save lwup200clr
real, dimension(:,:), allocatable, save rnebcon
real, dimension(:), allocatable, save albsol1
real, dimension(:,:,:), allocatable, save tsumstd
integer, dimension(:), allocatable, save lalim_conv
real, dimension(:,:), allocatable, save u2std
real, dimension(:,:,:), allocatable, save wtsumstd
real, dimension(:,:), allocatable, save v2std
real, dimension(:), allocatable, save rain_con
integer, parameter nlevstd3
real, dimension(:), allocatable, save solswp
real, dimension(:,:,:), allocatable, save tnondef
real, dimension(:), allocatable, save sollwdown
real, dimension(:,:), allocatable, save cool0
real, dimension(:), allocatable, save wake_s
real, dimension(:), allocatable, save ale_bl
real, dimension(:), allocatable, save wake_cstar
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL &zphi geo500!IM on interpole a chaque pas de temps le SWdn200clr CALL SWup200clr CALL & lwdn0
real, dimension(:), allocatable, save topsw0
real, dimension(:), allocatable, save snow_con
real, dimension(:,:), allocatable, save lwdn0p
real, dimension(:), allocatable, save chl_con
real, dimension(:), allocatable, save swup200
real, dimension(:), allocatable, save zvthe
real, dimension(:,:), allocatable, save philevstd
real, dimension(:,:), allocatable, save delta_tsurf
real, dimension(:,:,:), allocatable, save wsumstd
integer, parameter nbands_lw_rrtm
Definition: aero_mod.F90:96
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL &zphi geo500!IM on interpole a chaque pas de temps le SWdn200clr CALL & swup0
real, dimension(:), allocatable, save albplap
real, dimension(:,:,:), allocatable, save wake_delta_pbl_tke
real, dimension(:), allocatable, save alp_bl
real, dimension(:), allocatable, save ema_cbmf
real, dimension(:,:), allocatable, save heat0p
real, dimension(:), allocatable, save toplw
real, dimension(:,:,:), allocatable, save coefh
real, dimension(:,:), allocatable, save z0m
real, dimension(:,:,:), allocatable, save tr_ancien
real, dimension(:,:), allocatable, save pfrac_1nucl
real, dimension(:,:,:,:), allocatable, save piz_aero
real, dimension(:,:), allocatable, save lwdn
real, dimension(:,:,:,:), allocatable, save tau_aero_sw_rrtm
real, dimension(:,:), allocatable, save rhlevstd
real, dimension(:), allocatable, save rugoro
real, dimension(:), allocatable, save zpic
real, dimension(:), allocatable, save swradcorr
real, dimension(:,:,:), allocatable, save o3daysumstd
real, dimension(:), allocatable, save rlon
real, dimension(:,:), allocatable, save wght_th
real, dimension(:,:), allocatable, save fm_therm
real, dimension(:), allocatable, save topsw0p
real, dimension(:), allocatable, save solsw
real, dimension(:,:,:), allocatable, save uvsumstd
real, dimension(:), allocatable, save zgam
real, dimension(:,:,:), allocatable, save wo
real, dimension(:), allocatable, save wake_fip
integer, parameter nlevstd
real, dimension(:), allocatable, save toplw0
real, dimension(:), allocatable, save swdn200clr
real, dimension(:,:), allocatable, save pfrac_nucl
real, dimension(:), allocatable, save gustiness
real, dimension(:,:), allocatable, save u10m
real, dimension(:,:), allocatable, save vqstd
real, dimension(:), allocatable, save alb_neig
real, dimension(:,:,:,:), allocatable, save cg_aero_lw_rrtm
real, dimension(:,:), allocatable, save v10m
integer, parameter nbands_sw_rrtm
Definition: aero_mod.F90:95
real, dimension(:,:), allocatable, save clwcon0
real, dimension(:,:), allocatable, save swdn
real, dimension(:), allocatable, save ema_pct
real, dimension(:,:), allocatable, save lwupp
real, dimension(:,:,:), allocatable, save rhsumstd
real, dimension(:,:), allocatable, save qtc_cv
integer, parameter nout
real, dimension(:,:,:), allocatable, save coefm
real, dimension(:,:), allocatable, save sigt_cv
real, dimension(:,:,:), allocatable, save falb_dif
real, dimension(:), allocatable, save albsol2
integer, dimension(:,:), allocatable, save seed_old
integer, parameter nlevstd8
integer, save klevp1
Definition: dimphy.F90:8
integer, parameter nbsrf
real, dimension(:), allocatable, save rlat
real, dimension(:,:), allocatable, save wstar
real, dimension(:,:), allocatable, save ustar
real, dimension(:), allocatable, save ale
real, dimension(:), allocatable, save solswai
real, dimension(:,:), allocatable, save cool0p
real, dimension(:,:), allocatable, save du_gwd_rando
real, dimension(:), allocatable, save wake_pe
real, dimension(:,:,:), allocatable, save t2sumstd
real, dimension(:,:), allocatable, save coolp
real, dimension(:), allocatable, save cin
real, dimension(:,:), allocatable, save clwcon0th
real, dimension(:), allocatable, save toplwp
real, dimension(:), allocatable, save newsst
real, dimension(:,:), allocatable, save agesno
subroutine phys_state_var_init()
real, dimension(:,:), allocatable, save swup
real, dimension(:,:,:), allocatable, save usumstd
real, dimension(:,:,:,:), allocatable, save cg_aero_sw_rrtm
real, dimension(:,:,:), allocatable, save vphisumstd
real, dimension(:,:), allocatable, save ratqs
real, dimension(:), allocatable, save ale_bl_trig
real, dimension(:,:,:), allocatable, save qsumstd
real, dimension(:), allocatable, save zstd
real, dimension(:,:), allocatable, save swdnp
real, dimension(:), allocatable, save toplw0p
real, dimension(:,:), allocatable, save wqstd
real, dimension(:), allocatable, save lwup200
real, dimension(:,:), allocatable, save fevap
real, dimension(:), allocatable, save swdn200
real, dimension(:), allocatable, save zmax0
nrlmd
real, dimension(:), allocatable, save albpla
real, dimension(:), allocatable, save wd
real, dimension(:), allocatable, save lwdn200
real, dimension(:,:), allocatable, save z0h
real, dimension(:), allocatable, save sollw0p
real, dimension(:,:,:), allocatable, save wqsumstd
real, dimension(:,:), allocatable, save vlevstd
real, dimension(:,:), allocatable, save ftsol
real, dimension(:,:), allocatable, save ma
real, dimension(:), allocatable, save solswad
real, dimension(:,:), allocatable, save zqasc
Definition: dimphy.F90:1
real, dimension(:,:), allocatable, save swupp
real, dimension(:,:), allocatable, save lwup
real, dimension(:,:), allocatable, save u_ancien
real, dimension(:), allocatable, save lwdntoaclr
real, dimension(:), allocatable, save zthe
real, dimension(:,:), allocatable, save o3daystd
real, dimension(:,:), allocatable, save o3std
real, dimension(:), allocatable, save swup200clr
real, dimension(:,:,:), allocatable, save vtsumstd
!$Id!Parameters for nlm real sigd
Definition: cv30param.h:5
real, dimension(:), allocatable, save paire_ter
integer, parameter naero_grp
Definition: aero_mod.F90:64
real, dimension(:,:), allocatable, save ulevstd
real, dimension(:), allocatable, save alp
real, dimension(:,:), allocatable, save detr_therm
real, dimension(:,:), allocatable, save fqd
real, dimension(:,:), allocatable, save v_ancien
real, dimension(:), allocatable, save topswp
real, dimension(:), allocatable, save sollw0
real, dimension(:), allocatable, save radsolp
real, dimension(:), allocatable, save topswai
real, dimension(:,:), allocatable, save wake_deltat
real, dimension(:,:), allocatable, save albsol_dir