source: LMDZ4/branches/LMDZ4-dev/libf/phylmd/phys_state_var_mod.F90 @ 1278

Last change on this file since 1278 was 1263, checked in by lguez, 15 years ago

1) Reactivated ability to read ozone (that was deactivated because of
dependency on version of IOIPSL). Added ability to read a pressure
coordinate in Pa in "regr_lat_time_climoz".

2) Added the ability to read a second ozone climatology, corresponding to
daylight ozone:

-- "read_climoz" is now an integer variable, instead of a logical
variable.

-- Added argument "read_climoz" to "phys_state_var_init",
"phys_output_open" and "regr_lat_time_climoz".

-- Created new variable "ozone_daylight" for "hist*.nc" output files.

-- Added a third dimension to variable "wo" in module
"phys_state_var_mod" and variable "POZON" in "radlwsw": index 1 for
average day-night ozone, index 2 for daylight ozone.

-- Added a fourth dimension to variables "o3_in", "o3_regr_lat" and
"o3_out" in "regr_lat_time_climoz": index 1 for average day-night
ozone, index 2 for daylight ozone.

-- In "physiq", moved call to "conf_phys" before call to
"phys_state_var_init". Thus, "conf_phys" is now inside the block "if
(first)" instead of "IF (debut)". There were definitions of "bl95_b0"
and "bl95_b1" that were useless because the variables were overwritten
by "conf_phys". Removed those definitions.

-- In "radlwsw", we pass the average day-night ozone to "LW_LMDAR4"
and the daylight ozone, if we have it, to "SW_LMDAR4" or
"SW_AEROAR4". If we do not have a specific field for daylight ozone
then "SW_LMDAR4" or "SW_AEROAR4" just get the average day-night ozone.

-- "regr_lat_time_climoz" now manages latitudes where the input ozone
field is missing at all levels (polar night).

-- Encapsulated "radlwsw" in a module.

3) Modifications to make sequential and parallel versions of
"create_etat0_limit" almost identical:

-- In "dyn3dpar/create_etat0_limit.F". No need to call
"phys_state_var_init", removed "use phys_state_var_mod" statement. No
need for "clesphys.h", removed "include" statement.

-- In "dyn3dpar/etat0_netcdf.F". Added argument "tau_ratqs" in call to
"conf_phys" (this bug was already corrected in "dyn3d"). Moved call to
"inifilr" after call to "infotrac_init" (as in "dyn3d").

4) Other peripheral modifications:

-- Added procedures "nf95_get_att" and "nf95_def_var_scalar" in
NetCDF95 interface. Overloaded "nf95_put_var" with three more
procedures: "nf95_put_var_FourByteReal", "nf95_put_var_FourByteInt",
"nf95_put_var_1D_FourByteInt".

-- Overloaded "regr1_step_av" with one more procedure:
"regr14_step_av". Overloaded "regr3_lint" with one more procedure:
"regr34_lint".

-- Corrected call to "Init_Phys_lmdz" in "dyn3d/create_etat0_limit.F":
the last argument should be an array, not a scalar.

-- Encapsulated "conf_phys" in a module.

-- Splitted module "regr_pr" into "regr_pr_av_m" and "regr_pr_int_m".

5) Tests:

This revision was compared to revision 1259, with optimization options
"debug" and "dev", parallelization options "none", "mpi", "omp" and
"mpi_omp", 1 and 2 MPI processes, 1 and 2 OpenMP threads, with the
compiler "FORTRAN90/SX Version 2.0 for SX-8". Both programs
"create_etat0_limit" and "gcm" were tested. In all cases,
parallelization does not change the results. With "read_climoz = 0" in
the ".def" files, the results of revision 1259 and of this revision
are the same.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 18.3 KB
Line 
1      MODULE phys_state_var_mod
2! Variables sauvegardees pour le startphy.nc
3!======================================================================
4!
5!
6!======================================================================
7! Declaration des variables
8      USE dimphy
9      INTEGER, PARAMETER :: nlevSTD=17
10      INTEGER, PARAMETER :: nout=3
11      INTEGER, PARAMETER :: napisccp=1
12      INTEGER, SAVE :: radpas
13      REAL, SAVE :: dtime, solaire_etat0
14!$OMP THREADPRIVATE(radpas)
15!$OMP THREADPRIVATE(dtime, solaire_etat0)
16
17      REAL, ALLOCATABLE, SAVE :: rlat(:), rlon(:), pctsrf(:,:)
18!$OMP THREADPRIVATE(rlat, rlon, pctsrf)
19      REAL, ALLOCATABLE, SAVE :: ftsol(:,:)
20!$OMP THREADPRIVATE(ftsol)
21!      character(len=6), SAVE :: ocean
22!!!!!!$OMP THREADPRIVATE(ocean)
23!      logical, SAVE :: ok_veget
24!!!!!!$OMP THREADPRIVATE(ok_veget)
25      REAL, ALLOCATABLE, SAVE :: falb1(:,:), falb2(:,:)
26!$OMP THREADPRIVATE(falb1, falb2)
27      REAL, ALLOCATABLE, SAVE :: rain_fall(:), snow_fall(:)
28!$OMP THREADPRIVATE( rain_fall, snow_fall)
29      REAL, ALLOCATABLE, SAVE :: solsw(:), sollw(:)
30!$OMP THREADPRIVATE(solsw, sollw)
31      REAL, ALLOCATABLE, SAVE :: radsol(:)
32!$OMP THREADPRIVATE(radsol)
33
34!clesphy0 param physiq
35!
36! Parametres de l'Orographie a l'Echelle Sous-Maille (OESM):
37!
38      REAL, ALLOCATABLE, SAVE :: zmea(:), zstd(:), zsig(:), zgam(:)
39!$OMP THREADPRIVATE(zmea, zstd, zsig, zgam)
40      REAL, ALLOCATABLE, SAVE :: zthe(:), zpic(:), zval(:)
41!$OMP THREADPRIVATE(zthe, zpic, zval)
42!     REAL tabcntr0(100)
43      REAL, ALLOCATABLE, SAVE :: rugoro(:)
44!$OMP THREADPRIVATE(rugoro)
45      REAL, ALLOCATABLE, SAVE :: t_ancien(:,:), q_ancien(:,:)
46!$OMP THREADPRIVATE(t_ancien, q_ancien)
47      REAL, ALLOCATABLE, SAVE :: u_ancien(:,:), v_ancien(:,:)
48!$OMP THREADPRIVATE(u_ancien, v_ancien)
49      LOGICAL, SAVE :: ancien_ok
50!$OMP THREADPRIVATE(ancien_ok)
51      REAL, ALLOCATABLE, SAVE :: clwcon(:,:),rnebcon(:,:)
52!$OMP THREADPRIVATE(clwcon,rnebcon)
53      REAL, ALLOCATABLE, SAVE :: ratqs(:,:)
54!$OMP THREADPRIVATE(ratqs)
55      REAL, ALLOCATABLE, SAVE :: pbl_tke(:,:,:) ! turb kinetic energy
56!$OMP THREADPRIVATE(pbl_tke)
57      REAL, ALLOCATABLE, SAVE :: zmax0(:), f0(:) !
58!$OMP THREADPRIVATE(zmax0,f0)
59      REAL, ALLOCATABLE, SAVE :: ema_work1(:,:), ema_work2(:,:)
60!$OMP THREADPRIVATE(ema_work1,ema_work2)
61      REAL, ALLOCATABLE, SAVE :: entr_therm(:,:), fm_therm(:,:)
62!$OMP THREADPRIVATE(entr_therm,fm_therm)
63      REAL, ALLOCATABLE, SAVE :: detr_therm(:,:)
64!$OMP THREADPRIVATE(detr_therm)
65!IM 150408
66!     pour phsystoke avec thermiques
67      REAL,ALLOCATABLE,SAVE :: clwcon0th(:,:),rnebcon0th(:,:)
68!$OMP THREADPRIVATE(clwcon0th,rnebcon0th)
69! radiation outputs
70      REAL,ALLOCATABLE,SAVE :: swdn0(:,:), swdn(:,:)
71!$OMP THREADPRIVATE(swdn0,swdn)
72      REAL,ALLOCATABLE,SAVE :: swup0(:,:), swup(:,:)
73!$OMP THREADPRIVATE(swup0,swup)
74      REAL,ALLOCATABLE,SAVE :: SWdn200clr(:), SWdn200(:)
75!$OMP THREADPRIVATE(SWdn200clr,SWdn200)
76      REAL,ALLOCATABLE,SAVE :: SWup200clr(:), SWup200(:)
77!$OMP THREADPRIVATE(SWup200clr,SWup200)
78      REAL,ALLOCATABLE,SAVE :: lwdn0(:,:), lwdn(:,:)
79!$OMP THREADPRIVATE(lwdn0,lwdn)
80      REAL,ALLOCATABLE,SAVE :: lwup0(:,:), lwup(:,:)
81!$OMP THREADPRIVATE(lwup0,lwup)
82      REAL,ALLOCATABLE,SAVE :: LWdn200clr(:), LWdn200(:)
83!$OMP THREADPRIVATE(LWdn200clr,LWdn200)
84      REAL,ALLOCATABLE,SAVE :: LWup200clr(:), LWup200(:)
85!$OMP THREADPRIVATE(LWup200clr,LWup200)
86      REAL,ALLOCATABLE,SAVE :: LWdnTOA(:), LWdnTOAclr(:)
87!$OMP THREADPRIVATE(LWdnTOA,LWdnTOAclr)
88! pressure level
89      REAL,ALLOCATABLE,SAVE :: tsumSTD(:,:,:)
90!$OMP THREADPRIVATE(tsumSTD)
91      REAL,ALLOCATABLE,SAVE :: usumSTD(:,:,:), vsumSTD(:,:,:)
92!$OMP THREADPRIVATE(usumSTD,vsumSTD)
93      REAL,ALLOCATABLE,SAVE :: wsumSTD(:,:,:), phisumSTD(:,:,:)
94!$OMP THREADPRIVATE(wsumSTD,phisumSTD)
95      REAL,ALLOCATABLE,SAVE :: qsumSTD(:,:,:), rhsumSTD(:,:,:)
96!$OMP THREADPRIVATE(qsumSTD,rhsumSTD)
97      REAL,ALLOCATABLE,SAVE :: tnondef(:,:,:)
98!$OMP THREADPRIVATE(tnondef)
99      REAL,ALLOCATABLE,SAVE :: uvsumSTD(:,:,:)
100!$OMP THREADPRIVATE(uvsumSTD)
101      REAL,ALLOCATABLE,SAVE :: vqsumSTD(:,:,:)
102!$OMP THREADPRIVATE(vqsumSTD)
103      REAL,ALLOCATABLE,SAVE :: vTsumSTD(:,:,:)
104!$OMP THREADPRIVATE(vTsumSTD)
105      REAL,ALLOCATABLE,SAVE :: wqsumSTD(:,:,:)
106!$OMP THREADPRIVATE(wqsumSTD)
107      REAL,ALLOCATABLE,SAVE :: vphisumSTD(:,:,:)
108!$OMP THREADPRIVATE(vphisumSTD)
109      REAL,ALLOCATABLE,SAVE :: wTsumSTD(:,:,:)
110!$OMP THREADPRIVATE(wTsumSTD)
111      REAL,ALLOCATABLE,SAVE :: u2sumSTD(:,:,:)
112!$OMP THREADPRIVATE(u2sumSTD)
113      REAL,ALLOCATABLE,SAVE :: v2sumSTD(:,:,:)
114!$OMP THREADPRIVATE(v2sumSTD)
115      REAL,ALLOCATABLE,SAVE :: T2sumSTD(:,:,:)
116!$OMP THREADPRIVATE(T2sumSTD)
117      INTEGER,ALLOCATABLE,SAVE :: seed_old(:,:)
118!$OMP THREADPRIVATE(seed_old)
119      REAL,ALLOCATABLE,SAVE :: zuthe(:),zvthe(:)
120!$OMP THREADPRIVATE(zuthe,zvthe)
121      REAL,ALLOCATABLE,SAVE :: alb_neig(:)
122!$OMP THREADPRIVATE(alb_neig)
123!cloud base mass flux
124      REAL,ALLOCATABLE,SAVE :: ema_workcbmf(:), ema_cbmf(:)
125!$OMP THREADPRIVATE(ema_workcbmf,ema_cbmf)
126!cloud base pressure & cloud top pressure
127      REAL,ALLOCATABLE,SAVE :: ema_pcb(:), ema_pct(:)
128!$OMP THREADPRIVATE(ema_pcb,ema_pct)
129      REAL,ALLOCATABLE,SAVE :: Ma(:,:)        ! undilute upward mass flux
130!$OMP THREADPRIVATE(Ma)
131      REAL,ALLOCATABLE,SAVE :: qcondc(:,:)    ! in-cld water content from convect
132!$OMP THREADPRIVATE(qcondc)
133      REAL,ALLOCATABLE,SAVE :: wd(:) ! sb
134!$OMP THREADPRIVATE(wd)
135      REAL,ALLOCATABLE,SAVE :: sigd(:)
136!$OMP THREADPRIVATE(sigd)
137!
138      REAL,ALLOCATABLE,SAVE :: cin(:)
139!$OMP THREADPRIVATE(cin)
140! ftd : differential heating between wake and environment
141      REAL,ALLOCATABLE,SAVE :: ftd(:,:)
142!$OMP THREADPRIVATE(ftd)
143! fqd : differential moistening between wake and environment
144      REAL,ALLOCATABLE,SAVE :: fqd(:,:)     
145!$OMP THREADPRIVATE(fqd)
146!34EK
147! -- Variables de controle de ALE et ALP
148!ALE : Energie disponible pour soulevement : utilisee par la
149!      convection d'Emanuel pour le declenchement et la regulation
150      REAL,ALLOCATABLE,SAVE :: ALE(:)
151!$OMP THREADPRIVATE(ALE)
152!ALP : Puissance  disponible pour soulevement
153      REAL,ALLOCATABLE,SAVE :: ALP(:)
154!$OMP THREADPRIVATE(ALP)
155!
156! nouvelles variables pour le couplage convection-couche limite
157      REAL,ALLOCATABLE,SAVE :: Ale_bl(:)
158!$OMP THREADPRIVATE(Ale_bl)
159      REAL,ALLOCATABLE,SAVE :: Alp_bl(:)
160!$OMP THREADPRIVATE(Alp_bl)
161      INTEGER,ALLOCATABLE,SAVE :: lalim_conv(:)
162!$OMP THREADPRIVATE(lalim_conv)
163      REAL,ALLOCATABLE,SAVE :: wght_th(:,:)
164!$OMP THREADPRIVATE(wght_th)
165!
166! variables de la wake
167! wake_deltat : ecart de temperature avec la zone non perturbee
168! wake_deltaq : ecart d'humidite avec la zone non perturbee
169! wake_Cstar  : vitesse d'etalement de la poche
170! wake_s      : fraction surfacique occupee par la poche froide
171! wake_fip    : Gust Front Impinging power - ALP
172! dt_wake, dq_wake: LS tendencies due to wake
173      REAL,ALLOCATABLE,SAVE :: wake_deltat(:,:)
174!$OMP THREADPRIVATE(wake_deltat)
175      REAL,ALLOCATABLE,SAVE :: wake_deltaq(:,:)
176!$OMP THREADPRIVATE(wake_deltaq)
177      REAL,ALLOCATABLE,SAVE :: wake_Cstar(:)
178!$OMP THREADPRIVATE(wake_Cstar)
179      REAL,ALLOCATABLE,SAVE :: wake_s(:)
180!$OMP THREADPRIVATE(wake_s)
181      REAL,ALLOCATABLE,SAVE :: wake_fip(:)
182!$OMP THREADPRIVATE(wake_fip)
183      REAL,ALLOCATABLE,SAVE :: dt_wake(:,:)
184!$OMP THREADPRIVATE(dt_wake)
185      REAL,ALLOCATABLE,SAVE :: dq_wake(:,:)
186!$OMP THREADPRIVATE(dq_wake)
187!
188! pfrac_impa : Produits des coefs lessivage impaction
189! pfrac_nucl : Produits des coefs lessivage nucleation
190! pfrac_1nucl: Produits des coefs lessi nucl (alpha = 1)
191      REAL,ALLOCATABLE,SAVE :: pfrac_impa(:,:), pfrac_nucl(:,:)
192!$OMP THREADPRIVATE(pfrac_impa,pfrac_nucl)
193      REAL,ALLOCATABLE,SAVE :: pfrac_1nucl(:,:)
194!$OMP THREADPRIVATE(pfrac_1nucl)
195!
196      REAL,ALLOCATABLE,SAVE :: total_rain(:), nday_rain(:) 
197!$OMP THREADPRIVATE(total_rain,nday_rain)
198      REAL,ALLOCATABLE,SAVE :: paire_ter(:)
199!$OMP THREADPRIVATE(paire_ter)
200! albsol1: albedo du sol total pour SW visible
201! albsol2: albedo du sol total pour SW proche IR
202      REAL,ALLOCATABLE,SAVE :: albsol1(:), albsol2(:)
203!$OMP THREADPRIVATE(albsol1,albsol2)
204
205      REAL, ALLOCATABLE, SAVE:: wo(:, :, :)
206      ! column-density of ozone in a layer, in kilo-Dobsons
207      ! Third dimension has size 1 or 2.
208      ! "wo(:, :, 1)" is for the average day-night field,
209      ! "wo(:, :, 2)" is for daylight time.
210      !$OMP THREADPRIVATE(wo)
211
212! heat : chauffage solaire
213! heat0: chauffage solaire ciel clair
214! cool : refroidissement infrarouge
215! cool0 : refroidissement infrarouge ciel clair
216! sollwdown : downward LW flux at surface
217! sollwdownclr : downward CS LW flux at surface
218! toplwdown : downward CS LW flux at TOA
219! toplwdownclr : downward CS LW flux at TOA
220      REAL,ALLOCATABLE,SAVE :: clwcon0(:,:),rnebcon0(:,:)
221!$OMP THREADPRIVATE(clwcon0,rnebcon0)
222      REAL,ALLOCATABLE,SAVE :: heat(:,:)   
223!$OMP THREADPRIVATE(heat)
224      REAL,ALLOCATABLE,SAVE :: heat0(:,:)
225!$OMP THREADPRIVATE(heat0)
226      REAL,ALLOCATABLE,SAVE :: cool(:,:)
227!$OMP THREADPRIVATE(cool)
228      REAL,ALLOCATABLE,SAVE :: cool0(:,:)
229!$OMP THREADPRIVATE(cool0)
230      REAL,ALLOCATABLE,SAVE :: topsw(:), toplw(:)
231!$OMP THREADPRIVATE(topsw,toplw)
232      REAL,ALLOCATABLE,SAVE :: sollwdown(:)
233!$OMP THREADPRIVATE(sollwdown)
234      REAL,ALLOCATABLE,SAVE :: sollwdownclr(:)
235!$OMP THREADPRIVATE(sollwdownclr)
236      REAL,ALLOCATABLE,SAVE :: toplwdown(:)
237!$OMP THREADPRIVATE(toplwdown)
238      REAL,ALLOCATABLE,SAVE :: toplwdownclr(:)
239!$OMP THREADPRIVATE(toplwdownclr)
240      REAL,ALLOCATABLE,SAVE :: topsw0(:),toplw0(:),solsw0(:),sollw0(:)
241!$OMP THREADPRIVATE(topsw0,toplw0,solsw0,sollw0)
242      REAL,ALLOCATABLE,SAVE :: albpla(:)
243!$OMP THREADPRIVATE(albpla)
244! pbase : cloud base pressure
245! bbase : cloud base buoyancy
246      REAL,ALLOCATABLE,SAVE :: cape(:)
247!$OMP THREADPRIVATE(cape)
248      REAL,ALLOCATABLE,SAVE :: pbase(:)
249!$OMP THREADPRIVATE(pbase)
250      REAL,ALLOCATABLE,SAVE :: bbase(:)
251!$OMP THREADPRIVATE(bbase)
252!
253      REAL,SAVE,ALLOCATABLE :: zqasc(:,:)
254!$OMP THREADPRIVATE( zqasc)
255      INTEGER,ALLOCATABLE,SAVE :: ibas_con(:), itop_con(:)
256!$OMP THREADPRIVATE(ibas_con,itop_con)
257      REAL,SAVE,ALLOCATABLE :: rain_con(:)
258!$OMP THREADPRIVATE(rain_con)
259      REAL,SAVE,ALLOCATABLE :: snow_con(:)
260!$OMP THREADPRIVATE(snow_con)
261!
262      REAL,SAVE,ALLOCATABLE :: rlonPOS(:)
263!$OMP THREADPRIVATE(rlonPOS)
264      REAL,SAVE,ALLOCATABLE :: newsst(:)
265!$OMP THREADPRIVATE(newsst)
266      REAL,SAVE,ALLOCATABLE :: u10m(:,:), v10m(:,:)
267!$OMP THREADPRIVATE(u10m,v10m)
268!
269! ok_ade=T -ADE=topswad-topsw
270! ok_aie=T ->
271!       ok_ade=T -AIE=topswai-topswad
272!       ok_ade=F -AIE=topswai-topsw
273!
274!topswad, solswad : Aerosol direct effect
275      REAL,SAVE,ALLOCATABLE :: topswad(:), solswad(:)
276!$OMP THREADPRIVATE(topswad,solswad)
277!topswai, solswai : Aerosol indirect effect
278      REAL,SAVE,ALLOCATABLE :: topswai(:), solswai(:)
279!$OMP THREADPRIVATE(topswai,solswai)
280
281      REAL,SAVE,ALLOCATABLE :: tau_aero(:,:,:,:), piz_aero(:,:,:,:), cg_aero(:,:,:,:)
282!$OMP THREADPRIVATE(tau_aero, piz_aero, cg_aero)
283      REAL,SAVE,ALLOCATABLE :: ccm(:,:,:)
284!$OMP THREADPRIVATE(ccm)
285
286CONTAINS
287
288!======================================================================
289SUBROUTINE phys_state_var_init(read_climoz)
290use dimphy
291use aero_mod
292IMPLICIT NONE
293
294integer, intent(in)::  read_climoz
295! read ozone climatology
296! Allowed values are 0, 1 and 2
297! 0: do not read an ozone climatology
298! 1: read a single ozone climatology that will be used day and night
299! 2: read two ozone climatologies, the average day and night
300! climatology and the daylight climatology
301
302#include "indicesol.h"
303#include "control.h"
304      ALLOCATE(rlat(klon), rlon(klon))
305      ALLOCATE(pctsrf(klon,nbsrf))
306      ALLOCATE(ftsol(klon,nbsrf))
307      ALLOCATE(falb1(klon,nbsrf))
308      ALLOCATE(falb2(klon,nbsrf))
309      ALLOCATE(rain_fall(klon))
310      ALLOCATE(snow_fall(klon))
311      ALLOCATE(solsw(klon), sollw(klon))
312      ALLOCATE(radsol(klon))
313      ALLOCATE(zmea(klon), zstd(klon), zsig(klon), zgam(klon))
314      ALLOCATE(zthe(klon), zpic(klon), zval(klon))
315
316      ALLOCATE(rugoro(klon))
317      ALLOCATE(t_ancien(klon,klev), q_ancien(klon,klev))
318      ALLOCATE(u_ancien(klon,klev), v_ancien(klon,klev))
319      ALLOCATE(clwcon(klon,klev),rnebcon(klon,klev))
320      ALLOCATE(ratqs(klon,klev))
321      ALLOCATE(pbl_tke(klon,klev+1,nbsrf))
322      ALLOCATE(zmax0(klon), f0(klon))
323      ALLOCATE(ema_work1(klon,klev), ema_work2(klon,klev))
324      ALLOCATE(entr_therm(klon,klev), fm_therm(klon,klev+1))
325      ALLOCATE(detr_therm(klon,klev))
326!     pour phsystoke avec thermiques
327      ALLOCATE(clwcon0th(klon,klev),rnebcon0th(klon,klev))
328! radiation outputs
329      ALLOCATE(swdn0(klon,klevp1), swdn(klon,klevp1))
330      ALLOCATE(swup0(klon,klevp1), swup(klon,klevp1))
331      ALLOCATE(lwdn0(klon,klevp1), lwdn(klon,klevp1))
332      ALLOCATE(lwup0(klon,klevp1), lwup(klon,klevp1))
333      ALLOCATE(SWdn200clr(klon), SWdn200(klon))
334      ALLOCATE(SWup200clr(klon), SWup200(klon))
335      ALLOCATE(LWdn200clr(klon), LWdn200(klon))
336      ALLOCATE(LWup200clr(klon), LWup200(klon))
337      ALLOCATE(LWdnTOA(klon), LWdnTOAclr(klon))
338! pressure level
339      ALLOCATE(tsumSTD(klon,nlevSTD,nout))
340      ALLOCATE(usumSTD(klon,nlevSTD,nout), vsumSTD(klon,nlevSTD,nout))
341      ALLOCATE(wsumSTD(klon,nlevSTD,nout), phisumSTD(klon,nlevSTD,nout))
342      ALLOCATE(qsumSTD(klon,nlevSTD,nout), rhsumSTD(klon,nlevSTD,nout))
343      ALLOCATE(tnondef(klon,nlevSTD,nout))
344      ALLOCATE(uvsumSTD(klon,nlevSTD,nout))
345      ALLOCATE(vqsumSTD(klon,nlevSTD,nout))
346      ALLOCATE(vTsumSTD(klon,nlevSTD,nout))
347      ALLOCATE(wqsumSTD(klon,nlevSTD,nout))
348      ALLOCATE(vphisumSTD(klon,nlevSTD,nout))
349      ALLOCATE(wTsumSTD(klon,nlevSTD,nout))
350      ALLOCATE(u2sumSTD(klon,nlevSTD,nout))
351      ALLOCATE(v2sumSTD(klon,nlevSTD,nout))
352      ALLOCATE(T2sumSTD(klon,nlevSTD,nout))
353      ALLOCATE(seed_old(klon,napisccp))
354      ALLOCATE(zuthe(klon),zvthe(klon))
355      ALLOCATE(alb_neig(klon))
356!cloud base mass flux
357      ALLOCATE(ema_workcbmf(klon), ema_cbmf(klon))
358!cloud base pressure & cloud top pressure
359      ALLOCATE(ema_pcb(klon), ema_pct(klon))
360!
361      ALLOCATE(Ma(klon,klev))
362      ALLOCATE(qcondc(klon,klev))
363      ALLOCATE(wd(klon))
364      ALLOCATE(sigd(klon))
365      ALLOCATE(cin(klon), ALE(klon), ALP(klon))
366      ALLOCATE(ftd(klon,klev), fqd(klon,klev))
367      ALLOCATE(Ale_bl(klon))
368      ALLOCATE(Alp_bl(klon))
369      ALLOCATE(lalim_conv(klon))
370      ALLOCATE(wght_th(klon,klev))
371      ALLOCATE(wake_deltat(klon,klev), wake_deltaq(klon,klev))
372      ALLOCATE(wake_Cstar(klon), wake_s(klon), wake_fip(klon))
373      ALLOCATE(dt_wake(klon,klev), dq_wake(klon,klev))
374      ALLOCATE(pfrac_impa(klon,klev), pfrac_nucl(klon,klev))
375      ALLOCATE(pfrac_1nucl(klon,klev))
376      ALLOCATE(total_rain(klon), nday_rain(klon))
377      ALLOCATE(paire_ter(klon))
378      ALLOCATE(albsol1(klon), albsol2(klon))
379
380      if (read_climoz <= 1) then
381         ALLOCATE(wo(klon,klev, 1))
382      else
383         ! read_climoz == 2
384         ALLOCATE(wo(klon,klev, 2))
385      end if
386     
387      ALLOCATE(clwcon0(klon,klev),rnebcon0(klon,klev))
388      ALLOCATE(heat(klon,klev), heat0(klon,klev))
389      ALLOCATE(cool(klon,klev), cool0(klon,klev))
390      ALLOCATE(topsw(klon), toplw(klon))
391      ALLOCATE(sollwdown(klon), sollwdownclr(klon))
392      ALLOCATE(toplwdown(klon), toplwdownclr(klon))
393      ALLOCATE(topsw0(klon),toplw0(klon),solsw0(klon),sollw0(klon))
394      ALLOCATE(albpla(klon))
395      ALLOCATE(cape(klon))
396      ALLOCATE(pbase(klon),bbase(klon))
397      ALLOCATE(zqasc(klon,klev))
398      ALLOCATE(ibas_con(klon), itop_con(klon))
399      ALLOCATE(rain_con(klon), snow_con(klon))
400      ALLOCATE(rlonPOS(klon))
401      ALLOCATE(newsst(klon))
402      ALLOCATE(u10m(klon,nbsrf), v10m(klon,nbsrf))
403      ALLOCATE(topswad(klon), solswad(klon))
404      ALLOCATE(topswai(klon), solswai(klon))
405      ALLOCATE(tau_aero(klon,klev,naero_grp,nbands),piz_aero(klon,klev,naero_grp,nbands),cg_aero(klon,klev,naero_grp,nbands))
406      ALLOCATE(ccm(klon,klev,nbands))
407
408END SUBROUTINE phys_state_var_init
409
410!======================================================================
411SUBROUTINE phys_state_var_end
412use dimphy
413IMPLICIT NONE
414#include "indicesol.h"
415#include "control.h"
416
417      deallocate(rlat, rlon, pctsrf, ftsol, falb1, falb2)
418      deallocate(rain_fall, snow_fall, solsw, sollw, radsol)
419      deallocate(zmea, zstd, zsig, zgam)
420      deallocate(zthe, zpic, zval)
421      deallocate(rugoro, t_ancien, q_ancien, clwcon, rnebcon)
422      deallocate(        u_ancien, v_ancien                 )
423      deallocate(ratqs, pbl_tke)
424      deallocate(zmax0, f0)
425      deallocate(ema_work1, ema_work2)
426      deallocate(entr_therm, fm_therm)
427      deallocate(detr_therm)
428      deallocate(clwcon0th, rnebcon0th)
429! radiation outputs
430      deallocate(swdn0, swdn)
431      deallocate(swup0, swup)
432      deallocate(lwdn0, lwdn)
433      deallocate(lwup0, lwup)
434      deallocate(SWdn200clr, SWdn200)
435      deallocate(SWup200clr, SWup200)
436      deallocate(LWdn200clr, LWdn200)
437      deallocate(LWup200clr, LWup200)
438      deallocate(LWdnTOA, LWdnTOAclr)
439! pressure level
440      deallocate(tsumSTD)
441      deallocate(usumSTD, vsumSTD)
442      deallocate(wsumSTD, phisumSTD)
443      deallocate(tnondef)
444      deallocate(qsumSTD, rhsumSTD)
445      deallocate(uvsumSTD)
446      deallocate(vqsumSTD)
447      deallocate(vTsumSTD)
448      deallocate(wqsumSTD)
449      deallocate(vphisumSTD)
450      deallocate(wTsumSTD)
451      deallocate(u2sumSTD)
452      deallocate(v2sumSTD)
453      deallocate(T2sumSTD)
454      deallocate(seed_old)
455      deallocate(zuthe, zvthe)
456      deallocate(alb_neig)
457      deallocate(ema_workcbmf, ema_cbmf)
458      deallocate(ema_pcb, ema_pct)
459      deallocate(Ma, qcondc)
460      deallocate(wd, sigd)
461      deallocate(cin, ALE, ALP)
462      deallocate(ftd, fqd)
463      deallocate(Ale_bl, Alp_bl)
464      deallocate(lalim_conv, wght_th)
465      deallocate(wake_deltat, wake_deltaq)
466      deallocate(wake_Cstar, wake_s, wake_fip)
467      deallocate(dt_wake, dq_wake)
468      deallocate(pfrac_impa, pfrac_nucl)
469      deallocate(pfrac_1nucl)
470      deallocate(total_rain, nday_rain)
471      deallocate(paire_ter)
472      deallocate(albsol1, albsol2)
473      deallocate(wo)
474      deallocate(clwcon0,rnebcon0)
475      deallocate(heat, heat0)
476      deallocate(cool, cool0)
477      deallocate(topsw, toplw)
478      deallocate(sollwdown, sollwdownclr)
479      deallocate(toplwdown, toplwdownclr)
480      deallocate(topsw0,toplw0,solsw0,sollw0)
481      deallocate(albpla)
482      deallocate(cape)
483      deallocate(pbase,bbase)
484      deallocate(zqasc)
485      deallocate(ibas_con, itop_con)
486      deallocate(rain_con, snow_con)
487      deallocate(rlonPOS)
488      deallocate(newsst)
489      deallocate(u10m, v10m)
490      deallocate(topswad, solswad)
491      deallocate(topswai, solswai)
492      deallocate(tau_aero,piz_aero,cg_aero)
493      deallocate(ccm)
494       
495END SUBROUTINE phys_state_var_end
496
497      END MODULE phys_state_var_mod
Note: See TracBrowser for help on using the repository browser.