source: LMDZ5/trunk/libf/phylmd/phys_state_var_mod.F90 @ 1539

Last change on this file since 1539 was 1539, checked in by musat, 13 years ago

Ajouts CFMIP2/CMIP5

  • 6eme fichier de sortie "stations" histstn.nc qui necessite 2 fichiers (voir DefLists?): npCFMIP_param.data(_*) contenant le nombre de points (120 pour simulations AMIP, 73 pour aqua) pointlocations.txt(_*) contenant le numero, les coordonnees (lon,lat) et le nom de chaque station
  • flag LOGICAL dans tous les appels histwrite_phy pour pouvoir sortir le fichier histstn.nc

NB: 1) les flags de type phys_ que l'on met dans le physiq.def_L* pour ajouter plus de sorties

necessitent dorenavant 6 valeurs, la 6eme correspondant au fichier histstn.nc

2) par defaut le fichier histstn.nc ne sort pas; pour le sortir ajouter les lignes suivantes

dans physiq.def_L*

### Type de fichier : global (n) ou stations (y)
phys_out_filestations = n n n n n y

  • introduction de 2 jeux de flags pour les taux des GES; taux actuels avec suffixes _act, taux futurs avec "_per" avec 2 appels au rayonnement si taux "_per" different des taux "_act" (utiles pour diags. CFMIP 4CO2)
  • flags "betaCRF" pour calculs CRF pour experiences sensibilite proprietes optiques eau liquide nuageuse avec initialisations par defaut; sinon besoin de fichier beta_crf.data

Ajout flag LOGICAL lCOSP necessaire pour sortir un fichier stations
IM

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