/[lmdze]/trunk/phylmd/physiq.f
ViewVC logotype

Annotation of /trunk/phylmd/physiq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 56 - (hide annotations)
Tue Jan 10 19:02:02 2012 UTC (12 years, 4 months ago) by guez
Original Path: trunk/libf/phylmd/physiq.f90
File size: 71712 byte(s)
Imported "writehist.f" from LMDZ.

Moved module variable "histaveid" from "com_io_dyn" to "initdynav_m".

In "inithist", access directly module variables from "com_io_dyn"
instead of going through the arguments. Copying from LMDZ, write "u"
and scalar variables to separate files. Create a new variable for the
new file in "com_io_dyn". Copying from LMDZ, change the vertical axes
of the three files.

Removed some useless initializations in "dissip".

In "bilan_dyn", removed useless variable "time". Avoiding the
approximate test on "dt_cum" being a multiple of "dt_app", just
compute "ncum" from known usage of "bilan_dyn" and compute "dt_cum"
from "ncum". Change "periodav" from real to integer in
"conf_gcm_m". Since "day_step" is required to be a multiple of
"iperiod", so is "ncum".

1 guez 3 module physiq_m
2    
3     IMPLICIT none
4    
5     contains
6    
7 guez 47 SUBROUTINE physiq(lafin, rdayvrai, time, dtphys, paprs, play, pphi, pphis, &
8     u, v, t, qx, omega, d_u, d_v, d_t, d_qx, d_ps, dudyn, PVteta)
9 guez 3
10 guez 47 ! From phylmd/physiq.F, version 1.22 2006/02/20 09:38:28 (SVN revision 678)
11     ! Author: Z.X. Li (LMD/CNRS) 1993
12 guez 3
13 guez 49 ! This is the main procedure for the "physics" part of the program.
14 guez 3
15 guez 56 use aaam_bud_m, only: aaam_bud
16 guez 51 USE abort_gcm_m, ONLY: abort_gcm
17 guez 53 use ajsec_m, only: ajsec
18 guez 51 USE calendar, ONLY: ymds2ju
19 guez 52 use calltherm_m, only: calltherm
20 guez 51 USE clesphys, ONLY: cdhmax, cdmmax, co2_ppm, ecrit_hf, ecrit_ins, &
21     ecrit_mth, ecrit_reg, ecrit_tra, ksta, ksta_ter, ok_kzmin
22     USE clesphys2, ONLY: cycle_diurne, iflag_con, nbapp_rad, new_oliq, &
23     ok_orodr, ok_orolf, soil_model
24     USE clmain_m, ONLY: clmain
25     USE comgeomphy, ONLY: airephy, cuphy, cvphy
26     USE concvl_m, ONLY: concvl
27     USE conf_gcm_m, ONLY: offline, raz_date
28     USE conf_phys_m, ONLY: conf_phys
29     USE ctherm, ONLY: iflag_thermals, nsplit_thermals
30 guez 52 use diagcld2_m, only: diagcld2
31 guez 51 use diagetpq_m, only: diagetpq
32     USE dimens_m, ONLY: iim, jjm, llm, nqmx
33     USE dimphy, ONLY: klon, nbtr
34     USE dimsoil, ONLY: nsoilmx
35 guez 52 use drag_noro_m, only: drag_noro
36 guez 51 USE fcttre, ONLY: foeew, qsatl, qsats, thermcep
37     USE hgardfou_m, ONLY: hgardfou
38     USE histcom, ONLY: histsync
39     USE histwrite_m, ONLY: histwrite
40     USE indicesol, ONLY: clnsurf, epsfra, is_lic, is_oce, is_sic, is_ter, &
41     nbsrf
42     USE ini_histhf_m, ONLY: ini_histhf
43     USE ini_histday_m, ONLY: ini_histday
44     USE ini_histins_m, ONLY: ini_histins
45     USE oasis_m, ONLY: ok_oasis
46     USE orbite_m, ONLY: orbite, zenang
47     USE ozonecm_m, ONLY: ozonecm
48     USE phyetat0_m, ONLY: phyetat0, rlat, rlon
49     USE phyredem_m, ONLY: phyredem
50     USE phystokenc_m, ONLY: phystokenc
51     USE phytrac_m, ONLY: phytrac
52     USE qcheck_m, ONLY: qcheck
53 guez 53 use radlwsw_m, only: radlwsw
54 guez 54 use sugwd_m, only: sugwd
55 guez 51 USE suphec_m, ONLY: ra, rcpd, retv, rg, rlvtt, romega, rsigma, rtt
56     USE temps, ONLY: annee_ref, day_ref, itau_phy
57     USE yoethf_m, ONLY: r2es, rvtmp2
58 guez 3
59 guez 51 ! Arguments:
60 guez 3
61 guez 15 REAL, intent(in):: rdayvrai
62     ! (elapsed time since January 1st 0h of the starting year, in days)
63    
64 guez 47 REAL, intent(in):: time ! heure de la journée en fraction de jour
65     REAL, intent(in):: dtphys ! pas d'integration pour la physique (seconde)
66 guez 3 logical, intent(in):: lafin ! dernier passage
67    
68 guez 51 REAL, intent(in):: paprs(klon, llm + 1)
69 guez 3 ! (pression pour chaque inter-couche, en Pa)
70 guez 15
71 guez 47 REAL, intent(in):: play(klon, llm)
72 guez 3 ! (input pression pour le mileu de chaque couche (en Pa))
73    
74 guez 47 REAL, intent(in):: pphi(klon, llm)
75 guez 3 ! (input geopotentiel de chaque couche (g z) (reference sol))
76    
77 guez 51 REAL, intent(in):: pphis(klon) ! input geopotentiel du sol
78 guez 3
79 guez 47 REAL, intent(in):: u(klon, llm)
80     ! vitesse dans la direction X (de O a E) en m/s
81 guez 51
82 guez 47 REAL, intent(in):: v(klon, llm) ! vitesse Y (de S a N) en m/s
83 guez 51 REAL, intent(in):: t(klon, llm) ! input temperature (K)
84 guez 3
85 guez 34 REAL, intent(in):: qx(klon, llm, nqmx)
86     ! (humidité spécifique et fractions massiques des autres traceurs)
87 guez 3
88 guez 47 REAL omega(klon, llm) ! input vitesse verticale en Pa/s
89     REAL, intent(out):: d_u(klon, llm) ! tendance physique de "u" (m/s/s)
90     REAL, intent(out):: d_v(klon, llm) ! tendance physique de "v" (m/s/s)
91 guez 49 REAL, intent(out):: d_t(klon, llm) ! tendance physique de "t" (K/s)
92 guez 47 REAL d_qx(klon, llm, nqmx) ! output tendance physique de "qx" (kg/kg/s)
93     REAL d_ps(klon) ! output tendance physique de la pression au sol
94 guez 3
95 guez 35 LOGICAL:: firstcal = .true.
96    
97 guez 3 INTEGER nbteta
98 guez 51 PARAMETER(nbteta = 3)
99 guez 3
100     REAL PVteta(klon, nbteta)
101     ! (output vorticite potentielle a des thetas constantes)
102    
103 guez 47 LOGICAL ok_cvl ! pour activer le nouveau driver pour convection KE
104 guez 51 PARAMETER (ok_cvl = .TRUE.)
105 guez 3 LOGICAL ok_gust ! pour activer l'effet des gust sur flux surface
106 guez 51 PARAMETER (ok_gust = .FALSE.)
107 guez 3
108     LOGICAL check ! Verifier la conservation du modele en eau
109 guez 51 PARAMETER (check = .FALSE.)
110 guez 3
111 guez 51 LOGICAL, PARAMETER:: ok_stratus = .FALSE.
112 guez 49 ! Ajouter artificiellement les stratus
113    
114 guez 3 ! Parametres lies au coupleur OASIS:
115 guez 51 INTEGER, SAVE:: npas, nexca
116 guez 3 logical rnpb
117 guez 51 parameter(rnpb = .true.)
118 guez 3
119 guez 51 character(len = 6), save:: ocean
120 guez 12 ! (type de modèle océan à utiliser: "force" ou "slab" mais pas "couple")
121    
122 guez 3 logical ok_ocean
123     SAVE ok_ocean
124    
125 guez 49 ! "slab" ocean
126     REAL, save:: tslab(klon) ! temperature of ocean slab
127     REAL, save:: seaice(klon) ! glace de mer (kg/m2)
128     REAL fluxo(klon) ! flux turbulents ocean-glace de mer
129     REAL fluxg(klon) ! flux turbulents ocean-atmosphere
130 guez 3
131     ! Modele thermique du sol, a activer pour le cycle diurne:
132 guez 17 logical, save:: ok_veget
133     LOGICAL, save:: ok_journe ! sortir le fichier journalier
134 guez 3
135     LOGICAL ok_mensuel ! sortir le fichier mensuel
136    
137     LOGICAL ok_instan ! sortir le fichier instantane
138     save ok_instan
139    
140     LOGICAL ok_region ! sortir le fichier regional
141 guez 51 PARAMETER (ok_region = .FALSE.)
142 guez 3
143 guez 47 ! pour phsystoke avec thermiques
144 guez 51 REAL fm_therm(klon, llm + 1)
145 guez 3 REAL entr_therm(klon, llm)
146 guez 51 real, save:: q2(klon, llm + 1, nbsrf)
147 guez 3
148 guez 47 INTEGER ivap ! indice de traceurs pour vapeur d'eau
149 guez 51 PARAMETER (ivap = 1)
150 guez 47 INTEGER iliq ! indice de traceurs pour eau liquide
151 guez 51 PARAMETER (iliq = 2)
152 guez 3
153 guez 49 REAL, save:: t_ancien(klon, llm), q_ancien(klon, llm)
154     LOGICAL, save:: ancien_ok
155 guez 3
156     REAL d_t_dyn(klon, llm) ! tendance dynamique pour "t" (K/s)
157 guez 47 REAL d_q_dyn(klon, llm) ! tendance dynamique pour "q" (kg/kg/s)
158 guez 3
159     real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
160    
161     !IM Amip2 PV a theta constante
162    
163 guez 51 CHARACTER(LEN = 3) ctetaSTD(nbteta)
164 guez 3 DATA ctetaSTD/'350', '380', '405'/
165     REAL rtetaSTD(nbteta)
166     DATA rtetaSTD/350., 380., 405./
167    
168     !MI Amip2 PV a theta constante
169    
170     INTEGER klevp1
171 guez 51 PARAMETER(klevp1 = llm + 1)
172 guez 3
173     REAL swdn0(klon, klevp1), swdn(klon, klevp1)
174     REAL swup0(klon, klevp1), swup(klon, klevp1)
175     SAVE swdn0, swdn, swup0, swup
176    
177     REAL lwdn0(klon, klevp1), lwdn(klon, klevp1)
178     REAL lwup0(klon, klevp1), lwup(klon, klevp1)
179     SAVE lwdn0, lwdn, lwup0, lwup
180    
181     !IM Amip2
182     ! variables a une pression donnee
183    
184     integer nlevSTD
185 guez 51 PARAMETER(nlevSTD = 17)
186 guez 3 real rlevSTD(nlevSTD)
187     DATA rlevSTD/100000., 92500., 85000., 70000., &
188     60000., 50000., 40000., 30000., 25000., 20000., &
189     15000., 10000., 7000., 5000., 3000., 2000., 1000./
190 guez 51 CHARACTER(LEN = 4) clevSTD(nlevSTD)
191 guez 3 DATA clevSTD/'1000', '925 ', '850 ', '700 ', '600 ', &
192     '500 ', '400 ', '300 ', '250 ', '200 ', '150 ', '100 ', &
193 guez 47 '70 ', '50 ', '30 ', '20 ', '10 '/
194 guez 3
195     ! prw: precipitable water
196     real prw(klon)
197    
198     ! flwp, fiwp = Liquid Water Path & Ice Water Path (kg/m2)
199     ! flwc, fiwc = Liquid Water Content & Ice Water Content (kg/kg)
200     REAL flwp(klon), fiwp(klon)
201     REAL flwc(klon, llm), fiwc(klon, llm)
202    
203 guez 23 INTEGER kmax, lmax
204 guez 51 PARAMETER(kmax = 8, lmax = 8)
205 guez 3 INTEGER kmaxm1, lmaxm1
206 guez 51 PARAMETER(kmaxm1 = kmax-1, lmaxm1 = lmax-1)
207 guez 3
208     REAL zx_tau(kmaxm1), zx_pc(lmaxm1)
209     DATA zx_tau/0.0, 0.3, 1.3, 3.6, 9.4, 23., 60./
210     DATA zx_pc/50., 180., 310., 440., 560., 680., 800./
211    
212     ! cldtopres pression au sommet des nuages
213     REAL cldtopres(lmaxm1)
214     DATA cldtopres/50., 180., 310., 440., 560., 680., 800./
215    
216     ! taulev: numero du niveau de tau dans les sorties ISCCP
217 guez 51 CHARACTER(LEN = 4) taulev(kmaxm1)
218 guez 3
219     DATA taulev/'tau0', 'tau1', 'tau2', 'tau3', 'tau4', 'tau5', 'tau6'/
220 guez 51 CHARACTER(LEN = 3) pclev(lmaxm1)
221 guez 3 DATA pclev/'pc1', 'pc2', 'pc3', 'pc4', 'pc5', 'pc6', 'pc7'/
222    
223 guez 51 CHARACTER(LEN = 28) cnameisccp(lmaxm1, kmaxm1)
224 guez 3 DATA cnameisccp/'pc< 50hPa, tau< 0.3', 'pc= 50-180hPa, tau< 0.3', &
225     'pc= 180-310hPa, tau< 0.3', 'pc= 310-440hPa, tau< 0.3', &
226     'pc= 440-560hPa, tau< 0.3', 'pc= 560-680hPa, tau< 0.3', &
227     'pc= 680-800hPa, tau< 0.3', 'pc< 50hPa, tau= 0.3-1.3', &
228     'pc= 50-180hPa, tau= 0.3-1.3', 'pc= 180-310hPa, tau= 0.3-1.3', &
229     'pc= 310-440hPa, tau= 0.3-1.3', 'pc= 440-560hPa, tau= 0.3-1.3', &
230     'pc= 560-680hPa, tau= 0.3-1.3', 'pc= 680-800hPa, tau= 0.3-1.3', &
231     'pc< 50hPa, tau= 1.3-3.6', 'pc= 50-180hPa, tau= 1.3-3.6', &
232     'pc= 180-310hPa, tau= 1.3-3.6', 'pc= 310-440hPa, tau= 1.3-3.6', &
233     'pc= 440-560hPa, tau= 1.3-3.6', 'pc= 560-680hPa, tau= 1.3-3.6', &
234     'pc= 680-800hPa, tau= 1.3-3.6', 'pc< 50hPa, tau= 3.6-9.4', &
235     'pc= 50-180hPa, tau= 3.6-9.4', 'pc= 180-310hPa, tau= 3.6-9.4', &
236     'pc= 310-440hPa, tau= 3.6-9.4', 'pc= 440-560hPa, tau= 3.6-9.4', &
237     'pc= 560-680hPa, tau= 3.6-9.4', 'pc= 680-800hPa, tau= 3.6-9.4', &
238     'pc< 50hPa, tau= 9.4-23', 'pc= 50-180hPa, tau= 9.4-23', &
239     'pc= 180-310hPa, tau= 9.4-23', 'pc= 310-440hPa, tau= 9.4-23', &
240     'pc= 440-560hPa, tau= 9.4-23', 'pc= 560-680hPa, tau= 9.4-23', &
241     'pc= 680-800hPa, tau= 9.4-23', 'pc< 50hPa, tau= 23-60', &
242     'pc= 50-180hPa, tau= 23-60', 'pc= 180-310hPa, tau= 23-60', &
243     'pc= 310-440hPa, tau= 23-60', 'pc= 440-560hPa, tau= 23-60', &
244     'pc= 560-680hPa, tau= 23-60', 'pc= 680-800hPa, tau= 23-60', &
245     'pc< 50hPa, tau> 60.', 'pc= 50-180hPa, tau> 60.', &
246     'pc= 180-310hPa, tau> 60.', 'pc= 310-440hPa, tau> 60.', &
247     'pc= 440-560hPa, tau> 60.', 'pc= 560-680hPa, tau> 60.', &
248     'pc= 680-800hPa, tau> 60.'/
249    
250     !IM ISCCP simulator v3.4
251    
252     integer nid_hf, nid_hf3d
253     save nid_hf, nid_hf3d
254    
255     ! Variables propres a la physique
256    
257     INTEGER, save:: radpas
258     ! (Radiative transfer computations are made every "radpas" call to
259     ! "physiq".)
260    
261     REAL radsol(klon)
262 guez 47 SAVE radsol ! bilan radiatif au sol calcule par code radiatif
263 guez 3
264 guez 7 INTEGER, SAVE:: itap ! number of calls to "physiq"
265 guez 3
266 guez 49 REAL, save:: ftsol(klon, nbsrf) ! skin temperature of surface fraction
267 guez 3
268 guez 49 REAL, save:: ftsoil(klon, nsoilmx, nbsrf)
269     ! soil temperature of surface fraction
270 guez 3
271     REAL fevap(klon, nbsrf)
272 guez 47 SAVE fevap ! evaporation
273 guez 3 REAL fluxlat(klon, nbsrf)
274     SAVE fluxlat
275    
276     REAL fqsurf(klon, nbsrf)
277 guez 47 SAVE fqsurf ! humidite de l'air au contact de la surface
278 guez 3
279 guez 49 REAL, save:: qsol(klon) ! hauteur d'eau dans le sol
280 guez 3
281     REAL fsnow(klon, nbsrf)
282 guez 47 SAVE fsnow ! epaisseur neigeuse
283 guez 3
284     REAL falbe(klon, nbsrf)
285 guez 47 SAVE falbe ! albedo par type de surface
286 guez 3 REAL falblw(klon, nbsrf)
287 guez 47 SAVE falblw ! albedo par type de surface
288 guez 3
289 guez 13 ! Paramètres de l'orographie à l'échelle sous-maille (OESM) :
290     REAL, save:: zmea(klon) ! orographie moyenne
291     REAL, save:: zstd(klon) ! deviation standard de l'OESM
292     REAL, save:: zsig(klon) ! pente de l'OESM
293     REAL, save:: zgam(klon) ! anisotropie de l'OESM
294     REAL, save:: zthe(klon) ! orientation de l'OESM
295     REAL, save:: zpic(klon) ! Maximum de l'OESM
296     REAL, save:: zval(klon) ! Minimum de l'OESM
297     REAL, save:: rugoro(klon) ! longueur de rugosite de l'OESM
298 guez 3
299     REAL zulow(klon), zvlow(klon)
300    
301     INTEGER igwd, idx(klon), itest(klon)
302    
303     REAL agesno(klon, nbsrf)
304 guez 47 SAVE agesno ! age de la neige
305 guez 3
306     REAL run_off_lic_0(klon)
307     SAVE run_off_lic_0
308     !KE43
309     ! Variables liees a la convection de K. Emanuel (sb):
310    
311 guez 47 REAL bas, top ! cloud base and top levels
312 guez 3 SAVE bas
313     SAVE top
314    
315 guez 47 REAL Ma(klon, llm) ! undilute upward mass flux
316 guez 3 SAVE Ma
317 guez 47 REAL qcondc(klon, llm) ! in-cld water content from convect
318 guez 3 SAVE qcondc
319     REAL ema_work1(klon, llm), ema_work2(klon, llm)
320     SAVE ema_work1, ema_work2
321    
322     REAL wd(klon) ! sb
323 guez 47 SAVE wd ! sb
324 guez 3
325     ! Variables locales pour la couche limite (al1):
326    
327     ! Variables locales:
328    
329     REAL cdragh(klon) ! drag coefficient pour T and Q
330     REAL cdragm(klon) ! drag coefficient pour vent
331    
332 guez 47 !AA Pour phytrac
333     REAL ycoefh(klon, llm) ! coef d'echange pour phytrac
334     REAL yu1(klon) ! vents dans la premiere couche U
335     REAL yv1(klon) ! vents dans la premiere couche V
336     REAL ffonte(klon, nbsrf) !Flux thermique utilise pour fondre la neige
337 guez 3 REAL fqcalving(klon, nbsrf) !Flux d'eau "perdue" par la surface
338 guez 47 ! !et necessaire pour limiter la
339     ! !hauteur de neige, en kg/m2/s
340 guez 3 REAL zxffonte(klon), zxfqcalving(klon)
341    
342     REAL pfrac_impa(klon, llm)! Produits des coefs lessivage impaction
343     save pfrac_impa
344     REAL pfrac_nucl(klon, llm)! Produits des coefs lessivage nucleation
345     save pfrac_nucl
346     REAL pfrac_1nucl(klon, llm)! Produits des coefs lessi nucl (alpha = 1)
347     save pfrac_1nucl
348     REAL frac_impa(klon, llm) ! fractions d'aerosols lessivees (impaction)
349     REAL frac_nucl(klon, llm) ! idem (nucleation)
350    
351     !AA
352     REAL rain_fall(klon) ! pluie
353     REAL snow_fall(klon) ! neige
354     save snow_fall, rain_fall
355     !IM cf FH pour Tiedtke 080604
356     REAL rain_tiedtke(klon), snow_tiedtke(klon)
357    
358     REAL evap(klon), devap(klon) ! evaporation et sa derivee
359     REAL sens(klon), dsens(klon) ! chaleur sensible et sa derivee
360 guez 47 REAL dlw(klon) ! derivee infra rouge
361 guez 3 SAVE dlw
362     REAL bils(klon) ! bilan de chaleur au sol
363     REAL fder(klon) ! Derive de flux (sensible et latente)
364     save fder
365     REAL ve(klon) ! integr. verticale du transport meri. de l'energie
366     REAL vq(klon) ! integr. verticale du transport meri. de l'eau
367     REAL ue(klon) ! integr. verticale du transport zonal de l'energie
368     REAL uq(klon) ! integr. verticale du transport zonal de l'eau
369    
370     REAL frugs(klon, nbsrf) ! longueur de rugosite
371     save frugs
372     REAL zxrugs(klon) ! longueur de rugosite
373    
374     ! Conditions aux limites
375    
376     INTEGER julien
377    
378 guez 7 INTEGER, SAVE:: lmt_pas ! number of time steps of "physics" per day
379 guez 3 REAL pctsrf(klon, nbsrf)
380     !IM
381     REAL pctsrf_new(klon, nbsrf) !pourcentage surfaces issus d'ORCHIDEE
382    
383 guez 47 SAVE pctsrf ! sous-fraction du sol
384 guez 3 REAL albsol(klon)
385 guez 47 SAVE albsol ! albedo du sol total
386 guez 3 REAL albsollw(klon)
387 guez 47 SAVE albsollw ! albedo du sol total
388 guez 3
389 guez 17 REAL, SAVE:: wo(klon, llm) ! column density of ozone in a cell, in kDU
390 guez 3
391     ! Declaration des procedures appelees
392    
393 guez 47 EXTERNAL alboc ! calculer l'albedo sur ocean
394 guez 3 !KE43
395 guez 47 EXTERNAL conema3 ! convect4.3
396     EXTERNAL fisrtilp ! schema de condensation a grande echelle (pluie)
397     EXTERNAL nuage ! calculer les proprietes radiatives
398     EXTERNAL transp ! transport total de l'eau et de l'energie
399 guez 3
400     ! Variables locales
401    
402     real clwcon(klon, llm), rnebcon(klon, llm)
403     real clwcon0(klon, llm), rnebcon0(klon, llm)
404    
405     save rnebcon, clwcon
406    
407 guez 47 REAL rhcl(klon, llm) ! humiditi relative ciel clair
408     REAL dialiq(klon, llm) ! eau liquide nuageuse
409     REAL diafra(klon, llm) ! fraction nuageuse
410     REAL cldliq(klon, llm) ! eau liquide nuageuse
411     REAL cldfra(klon, llm) ! fraction nuageuse
412     REAL cldtau(klon, llm) ! epaisseur optique
413     REAL cldemi(klon, llm) ! emissivite infrarouge
414 guez 3
415 guez 47 REAL fluxq(klon, llm, nbsrf) ! flux turbulent d'humidite
416     REAL fluxt(klon, llm, nbsrf) ! flux turbulent de chaleur
417     REAL fluxu(klon, llm, nbsrf) ! flux turbulent de vitesse u
418     REAL fluxv(klon, llm, nbsrf) ! flux turbulent de vitesse v
419 guez 3
420     REAL zxfluxt(klon, llm)
421     REAL zxfluxq(klon, llm)
422     REAL zxfluxu(klon, llm)
423     REAL zxfluxv(klon, llm)
424    
425 guez 53 ! Le rayonnement n'est pas calcule tous les pas, il faut donc
426     ! que les variables soient rémanentes
427     REAL, save:: heat(klon, llm) ! chauffage solaire
428 guez 47 REAL heat0(klon, llm) ! chauffage solaire ciel clair
429     REAL cool(klon, llm) ! refroidissement infrarouge
430     REAL cool0(klon, llm) ! refroidissement infrarouge ciel clair
431 guez 3 REAL topsw(klon), toplw(klon), solsw(klon), sollw(klon)
432 guez 47 real sollwdown(klon) ! downward LW flux at surface
433 guez 3 REAL topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)
434     REAL albpla(klon)
435 guez 47 REAL fsollw(klon, nbsrf) ! bilan flux IR pour chaque sous surface
436     REAL fsolsw(klon, nbsrf) ! flux solaire absorb. pour chaque sous surface
437 guez 53 SAVE cool, albpla, topsw, toplw, solsw, sollw, sollwdown
438 guez 47 SAVE topsw0, toplw0, solsw0, sollw0, heat0, cool0
439 guez 3
440     INTEGER itaprad
441     SAVE itaprad
442    
443     REAL conv_q(klon, llm) ! convergence de l'humidite (kg/kg/s)
444 guez 49 REAL conv_t(klon, llm) ! convergence of temperature (K/s)
445 guez 3
446     REAL cldl(klon), cldm(klon), cldh(klon) !nuages bas, moyen et haut
447     REAL cldt(klon), cldq(klon) !nuage total, eau liquide integree
448    
449     REAL zxtsol(klon), zxqsurf(klon), zxsnow(klon), zxfluxlat(klon)
450    
451     REAL dist, rmu0(klon), fract(klon)
452     REAL zdtime ! pas de temps du rayonnement (s)
453     real zlongi
454    
455     REAL z_avant(klon), z_apres(klon), z_factor(klon)
456     LOGICAL zx_ajustq
457    
458     REAL za, zb
459 guez 51 REAL zx_t, zx_qs, zdelta, zcor
460 guez 3 real zqsat(klon, llm)
461     INTEGER i, k, iq, nsrf
462     REAL t_coup
463 guez 51 PARAMETER (t_coup = 234.0)
464 guez 3
465     REAL zphi(klon, llm)
466    
467     !IM cf. AM Variables locales pour la CLA (hbtm2)
468    
469 guez 49 REAL, SAVE:: pblh(klon, nbsrf) ! Hauteur de couche limite
470     REAL, SAVE:: plcl(klon, nbsrf) ! Niveau de condensation de la CLA
471     REAL, SAVE:: capCL(klon, nbsrf) ! CAPE de couche limite
472     REAL, SAVE:: oliqCL(klon, nbsrf) ! eau_liqu integree de couche limite
473     REAL, SAVE:: cteiCL(klon, nbsrf) ! cloud top instab. crit. couche limite
474     REAL, SAVE:: pblt(klon, nbsrf) ! T a la Hauteur de couche limite
475     REAL, SAVE:: therm(klon, nbsrf)
476     REAL, SAVE:: trmb1(klon, nbsrf) ! deep_cape
477     REAL, SAVE:: trmb2(klon, nbsrf) ! inhibition
478     REAL, SAVE:: trmb3(klon, nbsrf) ! Point Omega
479 guez 3 ! Grdeurs de sorties
480     REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)
481     REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)
482     REAL s_therm(klon), s_trmb1(klon), s_trmb2(klon)
483     REAL s_trmb3(klon)
484    
485     ! Variables locales pour la convection de K. Emanuel (sb):
486    
487 guez 47 REAL upwd(klon, llm) ! saturated updraft mass flux
488     REAL dnwd(klon, llm) ! saturated downdraft mass flux
489     REAL dnwd0(klon, llm) ! unsaturated downdraft mass flux
490     REAL tvp(klon, llm) ! virtual temp of lifted parcel
491     REAL cape(klon) ! CAPE
492 guez 3 SAVE cape
493    
494 guez 47 REAL pbase(klon) ! cloud base pressure
495 guez 3 SAVE pbase
496 guez 47 REAL bbase(klon) ! cloud base buoyancy
497 guez 3 SAVE bbase
498 guez 47 REAL rflag(klon) ! flag fonctionnement de convect
499     INTEGER iflagctrl(klon) ! flag fonctionnement de convect
500 guez 3 ! -- convect43:
501 guez 47 INTEGER ntra ! nb traceurs pour convect4.3
502 guez 3 REAL dtvpdt1(klon, llm), dtvpdq1(klon, llm)
503     REAL dplcldt(klon), dplcldr(klon)
504    
505     ! Variables du changement
506    
507     ! con: convection
508 guez 51 ! lsc: large scale condensation
509 guez 3 ! ajs: ajustement sec
510 guez 51 ! eva: évaporation de l'eau liquide nuageuse
511     ! vdf: vertical diffusion in boundary layer
512 guez 3 REAL d_t_con(klon, llm), d_q_con(klon, llm)
513     REAL d_u_con(klon, llm), d_v_con(klon, llm)
514     REAL d_t_lsc(klon, llm), d_q_lsc(klon, llm), d_ql_lsc(klon, llm)
515     REAL d_t_ajs(klon, llm), d_q_ajs(klon, llm)
516     REAL d_u_ajs(klon, llm), d_v_ajs(klon, llm)
517     REAL rneb(klon, llm)
518    
519     REAL pmfu(klon, llm), pmfd(klon, llm)
520     REAL pen_u(klon, llm), pen_d(klon, llm)
521     REAL pde_u(klon, llm), pde_d(klon, llm)
522     INTEGER kcbot(klon), kctop(klon), kdtop(klon)
523 guez 51 REAL pmflxr(klon, llm + 1), pmflxs(klon, llm + 1)
524     REAL prfl(klon, llm + 1), psfl(klon, llm + 1)
525 guez 3
526 guez 51 INTEGER,save:: ibas_con(klon), itop_con(klon)
527 guez 3
528     REAL rain_con(klon), rain_lsc(klon)
529     REAL snow_con(klon), snow_lsc(klon)
530     REAL d_ts(klon, nbsrf)
531    
532     REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)
533     REAL d_t_vdf(klon, llm), d_q_vdf(klon, llm)
534    
535     REAL d_u_oro(klon, llm), d_v_oro(klon, llm)
536     REAL d_t_oro(klon, llm)
537     REAL d_u_lif(klon, llm), d_v_lif(klon, llm)
538     REAL d_t_lif(klon, llm)
539    
540     REAL ratqs(klon, llm), ratqss(klon, llm), ratqsc(klon, llm)
541     real ratqsbas, ratqshaut
542     save ratqsbas, ratqshaut, ratqs
543    
544     ! Parametres lies au nouveau schema de nuages (SB, PDF)
545 guez 17 real, save:: fact_cldcon
546     real, save:: facttemps
547 guez 3 logical ok_newmicro
548     save ok_newmicro
549     real facteur
550    
551     integer iflag_cldcon
552     save iflag_cldcon
553    
554     logical ptconv(klon, llm)
555    
556 guez 51 ! Variables locales pour effectuer les appels en série :
557 guez 3
558     REAL t_seri(klon, llm), q_seri(klon, llm)
559     REAL ql_seri(klon, llm), qs_seri(klon, llm)
560     REAL u_seri(klon, llm), v_seri(klon, llm)
561    
562     REAL tr_seri(klon, llm, nbtr)
563     REAL d_tr(klon, llm, nbtr)
564    
565     REAL zx_rh(klon, llm)
566    
567     REAL zustrdr(klon), zvstrdr(klon)
568     REAL zustrli(klon), zvstrli(klon)
569     REAL zustrph(klon), zvstrph(klon)
570     REAL aam, torsfc
571    
572 guez 51 REAL dudyn(iim + 1, jjm + 1, llm)
573 guez 3
574 guez 47 REAL zx_tmp_fi2d(klon) ! variable temporaire grille physique
575 guez 3 REAL zx_tmp_2d(iim, jjm + 1), zx_tmp_3d(iim, jjm + 1, llm)
576    
577 guez 15 INTEGER, SAVE:: nid_day, nid_ins
578 guez 3
579     REAL ve_lay(klon, llm) ! transport meri. de l'energie a chaque niveau vert.
580     REAL vq_lay(klon, llm) ! transport meri. de l'eau a chaque niveau vert.
581     REAL ue_lay(klon, llm) ! transport zonal de l'energie a chaque niveau vert.
582     REAL uq_lay(klon, llm) ! transport zonal de l'eau a chaque niveau vert.
583    
584     REAL zsto
585    
586 guez 51 character(len = 20) modname
587     character(len = 80) abort_message
588 guez 3 logical ok_sync
589     real date0
590    
591 guez 51 ! Variables liées au bilan d'énergie et d'enthalpie :
592 guez 3 REAL ztsol(klon)
593 guez 47 REAL d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec
594 guez 51 REAL, SAVE:: d_h_vcol_phy
595 guez 47 REAL fs_bound, fq_bound
596     REAL zero_v(klon)
597 guez 51 CHARACTER(LEN = 15) ztit
598     INTEGER:: ip_ebil = 0 ! print level for energy conservation diagnostics
599 guez 18 INTEGER, SAVE:: if_ebil ! level for energy conservation diagnostics
600 guez 51
601     REAL d_t_ec(klon, llm) ! tendance due à la conversion Ec -> E thermique
602 guez 3 REAL ZRCPD
603 guez 51
604 guez 49 REAL t2m(klon, nbsrf), q2m(klon, nbsrf) ! temperature and humidity at 2 m
605 guez 3 REAL u10m(klon, nbsrf), v10m(klon, nbsrf) !vents a 10m
606 guez 47 REAL zt2m(klon), zq2m(klon) !temp., hum. 2m moyenne s/ 1 maille
607     REAL zu10m(klon), zv10m(klon) !vents a 10m moyennes s/1 maille
608     !jq Aerosol effects (Johannes Quaas, 27/11/2003)
609 guez 3 REAL sulfate(klon, llm) ! SO4 aerosol concentration [ug/m3]
610    
611 guez 49 REAL, save:: sulfate_pi(klon, llm)
612     ! (SO4 aerosol concentration, in ug/m3, pre-industrial value)
613 guez 3
614     REAL cldtaupi(klon, llm)
615     ! (Cloud optical thickness for pre-industrial (pi) aerosols)
616    
617 guez 47 REAL re(klon, llm) ! Cloud droplet effective radius
618     REAL fl(klon, llm) ! denominator of re
619 guez 3
620     ! Aerosol optical properties
621     REAL tau_ae(klon, llm, 2), piz_ae(klon, llm, 2)
622     REAL cg_ae(klon, llm, 2)
623    
624     REAL topswad(klon), solswad(klon) ! Aerosol direct effect.
625 guez 51 ! ok_ade = True -ADE = topswad-topsw
626 guez 3
627     REAL topswai(klon), solswai(klon) ! Aerosol indirect effect.
628 guez 51 ! ok_aie = True ->
629     ! ok_ade = True -AIE = topswai-topswad
630     ! ok_ade = F -AIE = topswai-topsw
631 guez 3
632 guez 47 REAL aerindex(klon) ! POLDER aerosol index
633 guez 3
634     ! Parameters
635 guez 47 LOGICAL ok_ade, ok_aie ! Apply aerosol (in)direct effects or not
636     REAL bl95_b0, bl95_b1 ! Parameter in Boucher and Lohmann (1995)
637 guez 3
638     SAVE ok_ade, ok_aie, bl95_b0, bl95_b1
639     SAVE u10m
640     SAVE v10m
641     SAVE t2m
642     SAVE q2m
643     SAVE ffonte
644     SAVE fqcalving
645     SAVE piz_ae
646     SAVE tau_ae
647     SAVE cg_ae
648     SAVE rain_con
649     SAVE snow_con
650     SAVE topswai
651     SAVE topswad
652     SAVE solswai
653     SAVE solswad
654     SAVE d_u_con
655     SAVE d_v_con
656     SAVE rnebcon0
657     SAVE clwcon0
658    
659 guez 17 real zmasse(klon, llm)
660     ! (column-density of mass of air in a cell, in kg m-2)
661    
662     real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
663    
664 guez 3 !----------------------------------------------------------------
665    
666     modname = 'physiq'
667     IF (if_ebil >= 1) THEN
668 guez 51 DO i = 1, klon
669     zero_v(i) = 0.
670 guez 3 END DO
671     END IF
672 guez 51 ok_sync = .TRUE.
673 guez 47 IF (nqmx < 2) THEN
674 guez 3 abort_message = 'eaux vapeur et liquide sont indispensables'
675 guez 13 CALL abort_gcm(modname, abort_message, 1)
676 guez 3 ENDIF
677    
678 guez 7 test_firstcal: IF (firstcal) THEN
679 guez 47 ! initialiser
680 guez 51 u10m = 0.
681     v10m = 0.
682     t2m = 0.
683     q2m = 0.
684     ffonte = 0.
685     fqcalving = 0.
686     piz_ae = 0.
687     tau_ae = 0.
688     cg_ae = 0.
689     rain_con(:) = 0.
690     snow_con(:) = 0.
691     bl95_b0 = 0.
692     bl95_b1 = 0.
693     topswai(:) = 0.
694     topswad(:) = 0.
695     solswai(:) = 0.
696     solswad(:) = 0.
697 guez 3
698 guez 13 d_u_con = 0.0
699     d_v_con = 0.0
700     rnebcon0 = 0.0
701     clwcon0 = 0.0
702     rnebcon = 0.0
703     clwcon = 0.0
704 guez 3
705 guez 47 pblh =0. ! Hauteur de couche limite
706     plcl =0. ! Niveau de condensation de la CLA
707     capCL =0. ! CAPE de couche limite
708     oliqCL =0. ! eau_liqu integree de couche limite
709     cteiCL =0. ! cloud top instab. crit. couche limite
710     pblt =0. ! T a la Hauteur de couche limite
711     therm =0.
712     trmb1 =0. ! deep_cape
713     trmb2 =0. ! inhibition
714     trmb3 =0. ! Point Omega
715 guez 3
716 guez 51 IF (if_ebil >= 1) d_h_vcol_phy = 0.
717 guez 3
718     ! appel a la lecture du run.def physique
719    
720     call conf_phys(ocean, ok_veget, ok_journe, ok_mensuel, &
721     ok_instan, fact_cldcon, facttemps, ok_newmicro, &
722     iflag_cldcon, ratqsbas, ratqshaut, if_ebil, &
723 guez 47 ok_ade, ok_aie, &
724 guez 3 bl95_b0, bl95_b1, &
725     iflag_thermals, nsplit_thermals)
726    
727     ! Initialiser les compteurs:
728    
729     frugs = 0.
730     itap = 0
731     itaprad = 0
732 guez 12 CALL phyetat0("startphy.nc", pctsrf, ftsol, ftsoil, ocean, tslab, &
733 guez 49 seaice, fqsurf, qsol, fsnow, falbe, falblw, fevap, rain_fall, &
734     snow_fall, solsw, sollwdown, dlw, radsol, frugs, agesno, zmea, &
735     zstd, zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, &
736     ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0)
737 guez 3
738 guez 47 ! ATTENTION : il faudra a terme relire q2 dans l'etat initial
739 guez 51 q2 = 1.e-8
740 guez 3
741 guez 49 radpas = NINT(86400. / dtphys / nbapp_rad)
742 guez 3
743     ! on remet le calendrier a zero
744 guez 15 IF (raz_date) itau_phy = 0
745 guez 3
746 guez 12 PRINT *, 'cycle_diurne = ', cycle_diurne
747 guez 3
748     IF(ocean.NE.'force ') THEN
749 guez 51 ok_ocean = .TRUE.
750 guez 3 ENDIF
751    
752 guez 12 CALL printflag(radpas, ok_ocean, ok_oasis, ok_journe, ok_instan, &
753     ok_region)
754 guez 3
755 guez 51 IF (dtphys*REAL(radpas) > 21600..AND.cycle_diurne) THEN
756 guez 12 print *,'Nbre d appels au rayonnement insuffisant'
757     print *,"Au minimum 4 appels par jour si cycle diurne"
758 guez 51 abort_message = 'Nbre d appels au rayonnement insuffisant'
759 guez 3 call abort_gcm(modname, abort_message, 1)
760     ENDIF
761 guez 51 print *,"Clef pour la convection, iflag_con = ", iflag_con
762     print *,"Clef pour le driver de la convection, ok_cvl = ", &
763 guez 3 ok_cvl
764    
765     ! Initialisation pour la convection de K.E. (sb):
766     IF (iflag_con >= 3) THEN
767    
768 guez 47 print *,"*** Convection de Kerry Emanuel 4.3 "
769 guez 3
770     !IM15/11/02 rajout initialisation ibas_con, itop_con cf. SB =>BEG
771     DO i = 1, klon
772     ibas_con(i) = 1
773     itop_con(i) = 1
774     ENDDO
775     !IM15/11/02 rajout initialisation ibas_con, itop_con cf. SB =>END
776    
777     ENDIF
778    
779     IF (ok_orodr) THEN
780 guez 13 rugoro = MAX(1e-5, zstd * zsig / 2)
781 guez 54 CALL SUGWD(paprs, play)
782 guez 13 else
783     rugoro = 0.
784 guez 3 ENDIF
785    
786 guez 47 lmt_pas = NINT(86400. / dtphys) ! tous les jours
787 guez 7 print *, 'Number of time steps of "physics" per day: ', lmt_pas
788 guez 3
789 guez 47 ecrit_ins = NINT(ecrit_ins/dtphys)
790     ecrit_hf = NINT(ecrit_hf/dtphys)
791     ecrit_mth = NINT(ecrit_mth/dtphys)
792     ecrit_tra = NINT(86400.*ecrit_tra/dtphys)
793     ecrit_reg = NINT(ecrit_reg/dtphys)
794 guez 3
795     ! Initialiser le couplage si necessaire
796    
797     npas = 0
798     nexca = 0
799    
800 guez 51 print *,'AVANT HIST IFLAG_CON = ', iflag_con
801 guez 3
802 guez 47 ! Initialisation des sorties
803 guez 3
804 guez 47 call ini_histhf(dtphys, nid_hf, nid_hf3d)
805     call ini_histday(dtphys, ok_journe, nid_day, nqmx)
806     call ini_histins(dtphys, ok_instan, nid_ins)
807 guez 3 CALL ymds2ju(annee_ref, 1, int(day_ref), 0., date0)
808     !XXXPB Positionner date0 pour initialisation de ORCHIDEE
809 guez 51 WRITE(*, *) 'physiq date0: ', date0
810 guez 7 ENDIF test_firstcal
811 guez 3
812     ! Mettre a zero des variables de sortie (pour securite)
813    
814     DO i = 1, klon
815     d_ps(i) = 0.0
816     ENDDO
817 guez 34 DO iq = 1, nqmx
818 guez 3 DO k = 1, llm
819     DO i = 1, klon
820     d_qx(i, k, iq) = 0.0
821     ENDDO
822     ENDDO
823     ENDDO
824 guez 51 da = 0.
825     mp = 0.
826     phi = 0.
827 guez 3
828 guez 51 ! Ne pas affecter les valeurs entrées de u, v, h, et q :
829 guez 3
830     DO k = 1, llm
831     DO i = 1, klon
832 guez 47 t_seri(i, k) = t(i, k)
833     u_seri(i, k) = u(i, k)
834     v_seri(i, k) = v(i, k)
835     q_seri(i, k) = qx(i, k, ivap)
836 guez 3 ql_seri(i, k) = qx(i, k, iliq)
837     qs_seri(i, k) = 0.
838     ENDDO
839     ENDDO
840 guez 34 IF (nqmx >= 3) THEN
841     tr_seri(:, :, :nqmx-2) = qx(:, :, 3:nqmx)
842 guez 3 ELSE
843     tr_seri(:, :, 1) = 0.
844     ENDIF
845    
846     DO i = 1, klon
847     ztsol(i) = 0.
848     ENDDO
849     DO nsrf = 1, nbsrf
850     DO i = 1, klon
851     ztsol(i) = ztsol(i) + ftsol(i, nsrf)*pctsrf(i, nsrf)
852     ENDDO
853     ENDDO
854    
855     IF (if_ebil >= 1) THEN
856 guez 51 ztit = 'after dynamics'
857 guez 47 CALL diagetpq(airephy, ztit, ip_ebil, 1, 1, dtphys, t_seri, q_seri, &
858     ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
859     d_ql, d_qs, d_ec)
860 guez 51 ! Comme les tendances de la physique sont ajoutés dans la
861     ! dynamique, la variation d'enthalpie par la dynamique devrait
862     ! être égale à la variation de la physique au pas de temps
863     ! précédent. Donc la somme de ces 2 variations devrait être
864     ! nulle.
865 guez 47 call diagphy(airephy, ztit, ip_ebil, zero_v, zero_v, zero_v, zero_v, &
866 guez 51 zero_v, zero_v, zero_v, zero_v, ztsol, d_h_vcol + d_h_vcol_phy, &
867 guez 49 d_qt, 0., fs_bound, fq_bound)
868 guez 3 END IF
869    
870 guez 51 ! Diagnostic de la tendance dynamique :
871 guez 3 IF (ancien_ok) THEN
872     DO k = 1, llm
873     DO i = 1, klon
874 guez 49 d_t_dyn(i, k) = (t_seri(i, k) - t_ancien(i, k)) / dtphys
875     d_q_dyn(i, k) = (q_seri(i, k) - q_ancien(i, k)) / dtphys
876 guez 3 ENDDO
877     ENDDO
878     ELSE
879     DO k = 1, llm
880     DO i = 1, klon
881     d_t_dyn(i, k) = 0.0
882     d_q_dyn(i, k) = 0.0
883     ENDDO
884     ENDDO
885     ancien_ok = .TRUE.
886     ENDIF
887    
888     ! Ajouter le geopotentiel du sol:
889     DO k = 1, llm
890     DO i = 1, klon
891     zphi(i, k) = pphi(i, k) + pphis(i)
892     ENDDO
893     ENDDO
894    
895 guez 49 ! Check temperatures:
896 guez 3 CALL hgardfou(t_seri, ftsol)
897    
898     ! Incrementer le compteur de la physique
899 guez 7 itap = itap + 1
900     julien = MOD(NINT(rdayvrai), 360)
901 guez 3 if (julien == 0) julien = 360
902    
903 guez 51 forall (k = 1: llm) zmasse(:, k) = (paprs(:, k)-paprs(:, k + 1)) / rg
904 guez 17
905 guez 3 ! Mettre en action les conditions aux limites (albedo, sst, etc.).
906 guez 49
907 guez 3 ! Prescrire l'ozone et calculer l'albedo sur l'ocean.
908 guez 34 if (nqmx >= 5) then
909 guez 18 wo = qx(:, :, 5) * zmasse / dobson_u / 1e3
910     else IF (MOD(itap - 1, lmt_pas) == 0) THEN
911 guez 22 wo = ozonecm(REAL(julien), paprs)
912 guez 3 ENDIF
913    
914 guez 51 ! Évaporation de l'eau liquide nuageuse :
915     DO k = 1, llm
916 guez 3 DO i = 1, klon
917 guez 51 zb = MAX(0., ql_seri(i, k))
918     t_seri(i, k) = t_seri(i, k) &
919     - zb * RLVTT / RCPD / (1. + RVTMP2 * q_seri(i, k))
920 guez 3 q_seri(i, k) = q_seri(i, k) + zb
921     ENDDO
922     ENDDO
923 guez 51 ql_seri = 0.
924 guez 3
925     IF (if_ebil >= 2) THEN
926 guez 51 ztit = 'after reevap'
927 guez 47 CALL diagetpq(airephy, ztit, ip_ebil, 2, 1, dtphys, t_seri, q_seri, &
928     ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
929     d_ql, d_qs, d_ec)
930     call diagphy(airephy, ztit, ip_ebil, zero_v, zero_v, zero_v, zero_v, &
931     zero_v, zero_v, zero_v, zero_v, ztsol, d_h_vcol, d_qt, d_ec, &
932 guez 49 fs_bound, fq_bound)
933 guez 3
934     END IF
935    
936     ! Appeler la diffusion verticale (programme de couche limite)
937    
938     DO i = 1, klon
939     zxrugs(i) = 0.0
940     ENDDO
941     DO nsrf = 1, nbsrf
942     DO i = 1, klon
943     frugs(i, nsrf) = MAX(frugs(i, nsrf), 0.000015)
944     ENDDO
945     ENDDO
946     DO nsrf = 1, nbsrf
947     DO i = 1, klon
948     zxrugs(i) = zxrugs(i) + frugs(i, nsrf)*pctsrf(i, nsrf)
949     ENDDO
950     ENDDO
951    
952     ! calculs necessaires au calcul de l'albedo dans l'interface
953    
954     CALL orbite(REAL(julien), zlongi, dist)
955     IF (cycle_diurne) THEN
956 guez 47 zdtime = dtphys * REAL(radpas)
957     CALL zenang(zlongi, time, zdtime, rmu0, fract)
958 guez 3 ELSE
959     rmu0 = -999.999
960     ENDIF
961    
962 guez 47 ! Calcul de l'abedo moyen par maille
963 guez 51 albsol(:) = 0.
964     albsollw(:) = 0.
965 guez 3 DO nsrf = 1, nbsrf
966     DO i = 1, klon
967     albsol(i) = albsol(i) + falbe(i, nsrf) * pctsrf(i, nsrf)
968     albsollw(i) = albsollw(i) + falblw(i, nsrf) * pctsrf(i, nsrf)
969     ENDDO
970     ENDDO
971    
972 guez 47 ! Repartition sous maille des flux LW et SW
973 guez 3 ! Repartition du longwave par sous-surface linearisee
974    
975     DO nsrf = 1, nbsrf
976     DO i = 1, klon
977     fsollw(i, nsrf) = sollw(i) &
978     + 4.0*RSIGMA*ztsol(i)**3 * (ztsol(i)-ftsol(i, nsrf))
979     fsolsw(i, nsrf) = solsw(i)*(1.-falbe(i, nsrf))/(1.-albsol(i))
980     ENDDO
981     ENDDO
982    
983     fder = dlw
984    
985 guez 38 ! Couche limite:
986 guez 3
987 guez 47 CALL clmain(dtphys, itap, date0, pctsrf, pctsrf_new, t_seri, q_seri, &
988 guez 40 u_seri, v_seri, julien, rmu0, co2_ppm, ok_veget, ocean, npas, nexca, &
989     ftsol, soil_model, cdmmax, cdhmax, ksta, ksta_ter, ok_kzmin, ftsoil, &
990 guez 47 qsol, paprs, play, fsnow, fqsurf, fevap, falbe, falblw, fluxlat, &
991 guez 40 rain_fall, snow_fall, fsolsw, fsollw, sollwdown, fder, rlon, rlat, &
992     cuphy, cvphy, frugs, firstcal, lafin, agesno, rugoro, d_t_vdf, &
993     d_q_vdf, d_u_vdf, d_v_vdf, d_ts, fluxt, fluxq, fluxu, fluxv, cdragh, &
994     cdragm, q2, dsens, devap, ycoefh, yu1, yv1, t2m, q2m, u10m, v10m, &
995     pblh, capCL, oliqCL, cteiCL, pblT, therm, trmb1, trmb2, trmb3, plcl, &
996     fqcalving, ffonte, run_off_lic_0, fluxo, fluxg, tslab, seaice)
997 guez 3
998 guez 40 ! Incrémentation des flux
999    
1000 guez 51 zxfluxt = 0.
1001     zxfluxq = 0.
1002     zxfluxu = 0.
1003     zxfluxv = 0.
1004 guez 3 DO nsrf = 1, nbsrf
1005     DO k = 1, llm
1006     DO i = 1, klon
1007 guez 47 zxfluxt(i, k) = zxfluxt(i, k) + &
1008 guez 49 fluxt(i, k, nsrf) * pctsrf(i, nsrf)
1009 guez 47 zxfluxq(i, k) = zxfluxq(i, k) + &
1010 guez 49 fluxq(i, k, nsrf) * pctsrf(i, nsrf)
1011 guez 47 zxfluxu(i, k) = zxfluxu(i, k) + &
1012 guez 49 fluxu(i, k, nsrf) * pctsrf(i, nsrf)
1013 guez 47 zxfluxv(i, k) = zxfluxv(i, k) + &
1014 guez 49 fluxv(i, k, nsrf) * pctsrf(i, nsrf)
1015 guez 3 END DO
1016     END DO
1017     END DO
1018     DO i = 1, klon
1019     sens(i) = - zxfluxt(i, 1) ! flux de chaleur sensible au sol
1020     evap(i) = - zxfluxq(i, 1) ! flux d'evaporation au sol
1021     fder(i) = dlw(i) + dsens(i) + devap(i)
1022     ENDDO
1023    
1024     DO k = 1, llm
1025     DO i = 1, klon
1026     t_seri(i, k) = t_seri(i, k) + d_t_vdf(i, k)
1027     q_seri(i, k) = q_seri(i, k) + d_q_vdf(i, k)
1028     u_seri(i, k) = u_seri(i, k) + d_u_vdf(i, k)
1029     v_seri(i, k) = v_seri(i, k) + d_v_vdf(i, k)
1030     ENDDO
1031     ENDDO
1032    
1033     IF (if_ebil >= 2) THEN
1034 guez 51 ztit = 'after clmain'
1035 guez 47 CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1036     ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1037     d_ql, d_qs, d_ec)
1038     call diagphy(airephy, ztit, ip_ebil, zero_v, zero_v, zero_v, zero_v, &
1039     sens, evap, zero_v, zero_v, ztsol, d_h_vcol, d_qt, d_ec, &
1040 guez 49 fs_bound, fq_bound)
1041 guez 3 END IF
1042    
1043 guez 49 ! Update surface temperature:
1044 guez 3
1045     DO i = 1, klon
1046     zxtsol(i) = 0.0
1047     zxfluxlat(i) = 0.0
1048    
1049     zt2m(i) = 0.0
1050     zq2m(i) = 0.0
1051     zu10m(i) = 0.0
1052     zv10m(i) = 0.0
1053     zxffonte(i) = 0.0
1054     zxfqcalving(i) = 0.0
1055    
1056     s_pblh(i) = 0.0
1057     s_lcl(i) = 0.0
1058     s_capCL(i) = 0.0
1059     s_oliqCL(i) = 0.0
1060     s_cteiCL(i) = 0.0
1061     s_pblT(i) = 0.0
1062     s_therm(i) = 0.0
1063     s_trmb1(i) = 0.0
1064     s_trmb2(i) = 0.0
1065     s_trmb3(i) = 0.0
1066    
1067 guez 49 IF (abs(pctsrf(i, is_ter) + pctsrf(i, is_lic) + &
1068 guez 51 pctsrf(i, is_oce) + pctsrf(i, is_sic) - 1.) > EPSFRA) &
1069 guez 3 THEN
1070 guez 47 WRITE(*, *) 'physiq : pb sous surface au point ', i, &
1071 guez 3 pctsrf(i, 1 : nbsrf)
1072     ENDIF
1073     ENDDO
1074     DO nsrf = 1, nbsrf
1075     DO i = 1, klon
1076     ftsol(i, nsrf) = ftsol(i, nsrf) + d_ts(i, nsrf)
1077     zxtsol(i) = zxtsol(i) + ftsol(i, nsrf)*pctsrf(i, nsrf)
1078     zxfluxlat(i) = zxfluxlat(i) + fluxlat(i, nsrf)*pctsrf(i, nsrf)
1079    
1080     zt2m(i) = zt2m(i) + t2m(i, nsrf)*pctsrf(i, nsrf)
1081     zq2m(i) = zq2m(i) + q2m(i, nsrf)*pctsrf(i, nsrf)
1082     zu10m(i) = zu10m(i) + u10m(i, nsrf)*pctsrf(i, nsrf)
1083     zv10m(i) = zv10m(i) + v10m(i, nsrf)*pctsrf(i, nsrf)
1084     zxffonte(i) = zxffonte(i) + ffonte(i, nsrf)*pctsrf(i, nsrf)
1085 guez 47 zxfqcalving(i) = zxfqcalving(i) + &
1086 guez 3 fqcalving(i, nsrf)*pctsrf(i, nsrf)
1087     s_pblh(i) = s_pblh(i) + pblh(i, nsrf)*pctsrf(i, nsrf)
1088     s_lcl(i) = s_lcl(i) + plcl(i, nsrf)*pctsrf(i, nsrf)
1089     s_capCL(i) = s_capCL(i) + capCL(i, nsrf) *pctsrf(i, nsrf)
1090     s_oliqCL(i) = s_oliqCL(i) + oliqCL(i, nsrf) *pctsrf(i, nsrf)
1091     s_cteiCL(i) = s_cteiCL(i) + cteiCL(i, nsrf) *pctsrf(i, nsrf)
1092     s_pblT(i) = s_pblT(i) + pblT(i, nsrf) *pctsrf(i, nsrf)
1093     s_therm(i) = s_therm(i) + therm(i, nsrf) *pctsrf(i, nsrf)
1094     s_trmb1(i) = s_trmb1(i) + trmb1(i, nsrf) *pctsrf(i, nsrf)
1095     s_trmb2(i) = s_trmb2(i) + trmb2(i, nsrf) *pctsrf(i, nsrf)
1096     s_trmb3(i) = s_trmb3(i) + trmb3(i, nsrf) *pctsrf(i, nsrf)
1097     ENDDO
1098     ENDDO
1099    
1100     ! Si une sous-fraction n'existe pas, elle prend la temp. moyenne
1101    
1102     DO nsrf = 1, nbsrf
1103     DO i = 1, klon
1104 guez 47 IF (pctsrf(i, nsrf) < epsfra) ftsol(i, nsrf) = zxtsol(i)
1105 guez 3
1106 guez 47 IF (pctsrf(i, nsrf) < epsfra) t2m(i, nsrf) = zt2m(i)
1107     IF (pctsrf(i, nsrf) < epsfra) q2m(i, nsrf) = zq2m(i)
1108     IF (pctsrf(i, nsrf) < epsfra) u10m(i, nsrf) = zu10m(i)
1109     IF (pctsrf(i, nsrf) < epsfra) v10m(i, nsrf) = zv10m(i)
1110     IF (pctsrf(i, nsrf) < epsfra) ffonte(i, nsrf) = zxffonte(i)
1111     IF (pctsrf(i, nsrf) < epsfra) &
1112 guez 3 fqcalving(i, nsrf) = zxfqcalving(i)
1113 guez 51 IF (pctsrf(i, nsrf) < epsfra) pblh(i, nsrf) = s_pblh(i)
1114     IF (pctsrf(i, nsrf) < epsfra) plcl(i, nsrf) = s_lcl(i)
1115     IF (pctsrf(i, nsrf) < epsfra) capCL(i, nsrf) = s_capCL(i)
1116     IF (pctsrf(i, nsrf) < epsfra) oliqCL(i, nsrf) = s_oliqCL(i)
1117     IF (pctsrf(i, nsrf) < epsfra) cteiCL(i, nsrf) = s_cteiCL(i)
1118     IF (pctsrf(i, nsrf) < epsfra) pblT(i, nsrf) = s_pblT(i)
1119     IF (pctsrf(i, nsrf) < epsfra) therm(i, nsrf) = s_therm(i)
1120     IF (pctsrf(i, nsrf) < epsfra) trmb1(i, nsrf) = s_trmb1(i)
1121     IF (pctsrf(i, nsrf) < epsfra) trmb2(i, nsrf) = s_trmb2(i)
1122     IF (pctsrf(i, nsrf) < epsfra) trmb3(i, nsrf) = s_trmb3(i)
1123 guez 3 ENDDO
1124     ENDDO
1125    
1126     ! Calculer la derive du flux infrarouge
1127    
1128     DO i = 1, klon
1129     dlw(i) = - 4.0*RSIGMA*zxtsol(i)**3
1130     ENDDO
1131    
1132     ! Appeler la convection (au choix)
1133    
1134     DO k = 1, llm
1135     DO i = 1, klon
1136 guez 47 conv_q(i, k) = d_q_dyn(i, k) &
1137     + d_q_vdf(i, k)/dtphys
1138     conv_t(i, k) = d_t_dyn(i, k) &
1139     + d_t_vdf(i, k)/dtphys
1140 guez 3 ENDDO
1141     ENDDO
1142     IF (check) THEN
1143     za = qcheck(klon, llm, paprs, q_seri, ql_seri, airephy)
1144 guez 51 print *, "avantcon = ", za
1145 guez 3 ENDIF
1146     zx_ajustq = .FALSE.
1147 guez 51 IF (iflag_con == 2) zx_ajustq = .TRUE.
1148 guez 3 IF (zx_ajustq) THEN
1149     DO i = 1, klon
1150     z_avant(i) = 0.0
1151     ENDDO
1152     DO k = 1, llm
1153     DO i = 1, klon
1154 guez 51 z_avant(i) = z_avant(i) + (q_seri(i, k) + ql_seri(i, k)) &
1155 guez 17 *zmasse(i, k)
1156 guez 3 ENDDO
1157     ENDDO
1158     ENDIF
1159 guez 51
1160     select case (iflag_con)
1161     case (1)
1162     print *, 'Réactiver l''appel à "conlmd" dans "physiq.F".'
1163     stop 1
1164     case (2)
1165     CALL conflx(dtphys, paprs, play, t_seri, q_seri, conv_t, conv_q, &
1166     zxfluxq(1, 1), omega, d_t_con, d_q_con, rain_con, snow_con, pmfu, &
1167     pmfd, pen_u, pde_u, pen_d, pde_d, kcbot, kctop, kdtop, pmflxr, &
1168     pmflxs)
1169 guez 3 WHERE (rain_con < 0.) rain_con = 0.
1170     WHERE (snow_con < 0.) snow_con = 0.
1171     DO i = 1, klon
1172 guez 51 ibas_con(i) = llm + 1 - kcbot(i)
1173     itop_con(i) = llm + 1 - kctop(i)
1174 guez 3 ENDDO
1175 guez 51 case (3:)
1176 guez 52 ! number of tracers for the convection scheme of Kerry Emanuel:
1177 guez 51 ! la partie traceurs est faite dans phytrac
1178     ! on met ntra = 1 pour limiter les appels mais on peut
1179 guez 3 ! supprimer les calculs / ftra.
1180     ntra = 1
1181 guez 51 ! Schéma de convection modularisé et vectorisé :
1182 guez 3 ! (driver commun aux versions 3 et 4)
1183    
1184 guez 51 IF (ok_cvl) THEN
1185     ! new driver for convectL
1186 guez 47 CALL concvl(iflag_con, dtphys, paprs, play, t_seri, q_seri, &
1187     u_seri, v_seri, tr_seri, ntra, ema_work1, ema_work2, d_t_con, &
1188     d_q_con, d_u_con, d_v_con, d_tr, rain_con, snow_con, ibas_con, &
1189     itop_con, upwd, dnwd, dnwd0, Ma, cape, tvp, iflagctrl, pbase, &
1190     bbase, dtvpdt1, dtvpdq1, dplcldt, dplcldr, qcondc, wd, pmflxr, &
1191     pmflxs, da, phi, mp)
1192 guez 51 clwcon0 = qcondc
1193     pmfu = upwd + dnwd
1194 guez 47 ELSE
1195 guez 51 ! conema3 ne contient pas les traceurs
1196 guez 52 CALL conema3(dtphys, paprs, play, t_seri, q_seri, u_seri, v_seri, &
1197 guez 51 tr_seri, ntra, ema_work1, ema_work2, d_t_con, d_q_con, &
1198     d_u_con, d_v_con, d_tr, rain_con, snow_con, ibas_con, &
1199     itop_con, upwd, dnwd, dnwd0, bas, top, Ma, cape, tvp, rflag, &
1200     pbase, bbase, dtvpdt1, dtvpdq1, dplcldt, dplcldr, clwcon0)
1201     ENDIF
1202 guez 3
1203     IF (.NOT. ok_gust) THEN
1204     do i = 1, klon
1205 guez 51 wd(i) = 0.0
1206 guez 3 enddo
1207     ENDIF
1208    
1209 guez 51 ! Calcul des propriétés des nuages convectifs
1210 guez 3
1211     DO k = 1, llm
1212     DO i = 1, klon
1213     zx_t = t_seri(i, k)
1214     IF (thermcep) THEN
1215     zdelta = MAX(0., SIGN(1., rtt-zx_t))
1216 guez 47 zx_qs = r2es * FOEEW(zx_t, zdelta)/play(i, k)
1217     zx_qs = MIN(0.5, zx_qs)
1218     zcor = 1./(1.-retv*zx_qs)
1219     zx_qs = zx_qs*zcor
1220 guez 3 ELSE
1221 guez 7 IF (zx_t < t_coup) THEN
1222 guez 47 zx_qs = qsats(zx_t)/play(i, k)
1223 guez 3 ELSE
1224 guez 47 zx_qs = qsatl(zx_t)/play(i, k)
1225 guez 3 ENDIF
1226     ENDIF
1227 guez 51 zqsat(i, k) = zx_qs
1228 guez 3 ENDDO
1229     ENDDO
1230    
1231 guez 47 ! calcul des proprietes des nuages convectifs
1232 guez 51 clwcon0 = fact_cldcon*clwcon0
1233 guez 3 call clouds_gno &
1234     (klon, llm, q_seri, zqsat, clwcon0, ptconv, ratqsc, rnebcon0)
1235 guez 51 case default
1236 guez 12 print *, "iflag_con non-prevu", iflag_con
1237 guez 3 stop 1
1238 guez 51 END select
1239 guez 3
1240     DO k = 1, llm
1241     DO i = 1, klon
1242     t_seri(i, k) = t_seri(i, k) + d_t_con(i, k)
1243     q_seri(i, k) = q_seri(i, k) + d_q_con(i, k)
1244     u_seri(i, k) = u_seri(i, k) + d_u_con(i, k)
1245     v_seri(i, k) = v_seri(i, k) + d_v_con(i, k)
1246     ENDDO
1247     ENDDO
1248    
1249     IF (if_ebil >= 2) THEN
1250 guez 51 ztit = 'after convect'
1251 guez 47 CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1252     ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1253     d_ql, d_qs, d_ec)
1254     call diagphy(airephy, ztit, ip_ebil, zero_v, zero_v, zero_v, zero_v, &
1255     zero_v, zero_v, rain_con, snow_con, ztsol, d_h_vcol, d_qt, d_ec, &
1256 guez 49 fs_bound, fq_bound)
1257 guez 3 END IF
1258    
1259     IF (check) THEN
1260     za = qcheck(klon, llm, paprs, q_seri, ql_seri, airephy)
1261 guez 51 print *,"aprescon = ", za
1262 guez 3 zx_t = 0.0
1263     za = 0.0
1264     DO i = 1, klon
1265     za = za + airephy(i)/REAL(klon)
1266     zx_t = zx_t + (rain_con(i)+ &
1267     snow_con(i))*airephy(i)/REAL(klon)
1268     ENDDO
1269 guez 47 zx_t = zx_t/za*dtphys
1270 guez 51 print *,"Precip = ", zx_t
1271 guez 3 ENDIF
1272     IF (zx_ajustq) THEN
1273     DO i = 1, klon
1274     z_apres(i) = 0.0
1275     ENDDO
1276     DO k = 1, llm
1277     DO i = 1, klon
1278 guez 51 z_apres(i) = z_apres(i) + (q_seri(i, k) + ql_seri(i, k)) &
1279 guez 17 *zmasse(i, k)
1280 guez 3 ENDDO
1281     ENDDO
1282     DO i = 1, klon
1283 guez 51 z_factor(i) = (z_avant(i)-(rain_con(i) + snow_con(i))*dtphys) &
1284 guez 3 /z_apres(i)
1285     ENDDO
1286     DO k = 1, llm
1287     DO i = 1, klon
1288 guez 52 IF (z_factor(i) > 1. + 1E-8 .OR. z_factor(i) < 1. - 1E-8) THEN
1289 guez 3 q_seri(i, k) = q_seri(i, k) * z_factor(i)
1290     ENDIF
1291     ENDDO
1292     ENDDO
1293     ENDIF
1294 guez 51 zx_ajustq = .FALSE.
1295 guez 3
1296 guez 51 ! Convection sèche (thermiques ou ajustement)
1297 guez 3
1298 guez 51 d_t_ajs = 0.
1299     d_u_ajs = 0.
1300     d_v_ajs = 0.
1301     d_q_ajs = 0.
1302     fm_therm = 0.
1303     entr_therm = 0.
1304 guez 3
1305 guez 47 if (iflag_thermals == 0) then
1306     ! Ajustement sec
1307     CALL ajsec(paprs, play, t_seri, q_seri, d_t_ajs, d_q_ajs)
1308 guez 13 t_seri = t_seri + d_t_ajs
1309     q_seri = q_seri + d_q_ajs
1310 guez 3 else
1311 guez 47 ! Thermiques
1312     call calltherm(dtphys, play, paprs, pphi, u_seri, v_seri, t_seri, &
1313     q_seri, d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm)
1314 guez 3 endif
1315    
1316     IF (if_ebil >= 2) THEN
1317 guez 51 ztit = 'after dry_adjust'
1318 guez 47 CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1319     ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1320     d_ql, d_qs, d_ec)
1321 guez 3 END IF
1322    
1323 guez 47 ! Caclul des ratqs
1324 guez 3
1325 guez 51 ! ratqs convectifs a l'ancienne en fonction de q(z = 0)-q / q
1326 guez 47 ! on ecrase le tableau ratqsc calcule par clouds_gno
1327 guez 3 if (iflag_cldcon == 1) then
1328 guez 51 do k = 1, llm
1329     do i = 1, klon
1330 guez 3 if(ptconv(i, k)) then
1331 guez 51 ratqsc(i, k) = ratqsbas &
1332 guez 3 +fact_cldcon*(q_seri(i, 1)-q_seri(i, k))/q_seri(i, k)
1333     else
1334 guez 51 ratqsc(i, k) = 0.
1335 guez 3 endif
1336     enddo
1337     enddo
1338     endif
1339    
1340 guez 47 ! ratqs stables
1341 guez 51 do k = 1, llm
1342     do i = 1, klon
1343     ratqss(i, k) = ratqsbas + (ratqshaut-ratqsbas)* &
1344 guez 47 min((paprs(i, 1)-play(i, k))/(paprs(i, 1)-30000.), 1.)
1345 guez 3 enddo
1346     enddo
1347    
1348 guez 47 ! ratqs final
1349 guez 3 if (iflag_cldcon == 1 .or.iflag_cldcon == 2) then
1350 guez 47 ! les ratqs sont une conbinaison de ratqss et ratqsc
1351     ! ratqs final
1352     ! 1e4 (en gros 3 heures), en dur pour le moment, est le temps de
1353     ! relaxation des ratqs
1354 guez 51 facteur = exp(-dtphys*facttemps)
1355     ratqs = max(ratqs*facteur, ratqss)
1356     ratqs = max(ratqs, ratqsc)
1357 guez 3 else
1358 guez 47 ! on ne prend que le ratqs stable pour fisrtilp
1359 guez 51 ratqs = ratqss
1360 guez 3 endif
1361    
1362 guez 51 ! Processus de condensation à grande echelle et processus de
1363     ! précipitation :
1364     CALL fisrtilp(dtphys, paprs, play, t_seri, q_seri, ptconv, ratqs, &
1365     d_t_lsc, d_q_lsc, d_ql_lsc, rneb, cldliq, rain_lsc, snow_lsc, &
1366     pfrac_impa, pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, &
1367     psfl, rhcl)
1368 guez 3
1369     WHERE (rain_lsc < 0) rain_lsc = 0.
1370     WHERE (snow_lsc < 0) snow_lsc = 0.
1371     DO k = 1, llm
1372     DO i = 1, klon
1373     t_seri(i, k) = t_seri(i, k) + d_t_lsc(i, k)
1374     q_seri(i, k) = q_seri(i, k) + d_q_lsc(i, k)
1375     ql_seri(i, k) = ql_seri(i, k) + d_ql_lsc(i, k)
1376     cldfra(i, k) = rneb(i, k)
1377     IF (.NOT.new_oliq) cldliq(i, k) = ql_seri(i, k)
1378     ENDDO
1379     ENDDO
1380     IF (check) THEN
1381     za = qcheck(klon, llm, paprs, q_seri, ql_seri, airephy)
1382 guez 51 print *,"apresilp = ", za
1383 guez 3 zx_t = 0.0
1384     za = 0.0
1385     DO i = 1, klon
1386     za = za + airephy(i)/REAL(klon)
1387     zx_t = zx_t + (rain_lsc(i) &
1388     + snow_lsc(i))*airephy(i)/REAL(klon)
1389     ENDDO
1390 guez 47 zx_t = zx_t/za*dtphys
1391 guez 51 print *,"Precip = ", zx_t
1392 guez 3 ENDIF
1393    
1394     IF (if_ebil >= 2) THEN
1395 guez 51 ztit = 'after fisrt'
1396 guez 47 CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1397     ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1398     d_ql, d_qs, d_ec)
1399     call diagphy(airephy, ztit, ip_ebil, zero_v, zero_v, zero_v, zero_v, &
1400     zero_v, zero_v, rain_lsc, snow_lsc, ztsol, d_h_vcol, d_qt, d_ec, &
1401 guez 49 fs_bound, fq_bound)
1402 guez 3 END IF
1403    
1404 guez 47 ! PRESCRIPTION DES NUAGES POUR LE RAYONNEMENT
1405 guez 3
1406     ! 1. NUAGES CONVECTIFS
1407    
1408     IF (iflag_cldcon.le.-1) THEN ! seulement pour Tiedtke
1409 guez 51 snow_tiedtke = 0.
1410 guez 3 if (iflag_cldcon == -1) then
1411 guez 51 rain_tiedtke = rain_con
1412 guez 3 else
1413 guez 51 rain_tiedtke = 0.
1414     do k = 1, llm
1415     do i = 1, klon
1416 guez 7 if (d_q_con(i, k) < 0.) then
1417 guez 51 rain_tiedtke(i) = rain_tiedtke(i)-d_q_con(i, k)/dtphys &
1418 guez 17 *zmasse(i, k)
1419 guez 3 endif
1420     enddo
1421     enddo
1422     endif
1423    
1424     ! Nuages diagnostiques pour Tiedtke
1425 guez 47 CALL diagcld1(paprs, play, &
1426 guez 3 rain_tiedtke, snow_tiedtke, ibas_con, itop_con, &
1427     diafra, dialiq)
1428     DO k = 1, llm
1429     DO i = 1, klon
1430 guez 51 IF (diafra(i, k) > cldfra(i, k)) THEN
1431 guez 3 cldliq(i, k) = dialiq(i, k)
1432     cldfra(i, k) = diafra(i, k)
1433     ENDIF
1434     ENDDO
1435     ENDDO
1436     ELSE IF (iflag_cldcon == 3) THEN
1437 guez 7 ! On prend pour les nuages convectifs le max du calcul de la
1438     ! convection et du calcul du pas de temps précédent diminué d'un facteur
1439     ! facttemps
1440 guez 47 facteur = dtphys *facttemps
1441 guez 51 do k = 1, llm
1442     do i = 1, klon
1443     rnebcon(i, k) = rnebcon(i, k)*facteur
1444     if (rnebcon0(i, k)*clwcon0(i, k) > rnebcon(i, k)*clwcon(i, k)) &
1445 guez 3 then
1446 guez 51 rnebcon(i, k) = rnebcon0(i, k)
1447     clwcon(i, k) = clwcon0(i, k)
1448 guez 3 endif
1449     enddo
1450     enddo
1451    
1452 guez 47 ! On prend la somme des fractions nuageuses et des contenus en eau
1453 guez 51 cldfra = min(max(cldfra, rnebcon), 1.)
1454     cldliq = cldliq + rnebcon*clwcon
1455 guez 3 ENDIF
1456    
1457 guez 51 ! 2. Nuages stratiformes
1458 guez 3
1459     IF (ok_stratus) THEN
1460 guez 47 CALL diagcld2(paprs, play, t_seri, q_seri, diafra, dialiq)
1461 guez 3 DO k = 1, llm
1462     DO i = 1, klon
1463 guez 51 IF (diafra(i, k) > cldfra(i, k)) THEN
1464 guez 3 cldliq(i, k) = dialiq(i, k)
1465     cldfra(i, k) = diafra(i, k)
1466     ENDIF
1467     ENDDO
1468     ENDDO
1469     ENDIF
1470    
1471     ! Precipitation totale
1472    
1473     DO i = 1, klon
1474     rain_fall(i) = rain_con(i) + rain_lsc(i)
1475     snow_fall(i) = snow_con(i) + snow_lsc(i)
1476     ENDDO
1477    
1478     IF (if_ebil >= 2) THEN
1479 guez 51 ztit = "after diagcld"
1480 guez 47 CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1481     ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1482     d_ql, d_qs, d_ec)
1483 guez 3 END IF
1484    
1485 guez 52 ! Humidité relative pour diagnostic:
1486 guez 3 DO k = 1, llm
1487     DO i = 1, klon
1488     zx_t = t_seri(i, k)
1489     IF (thermcep) THEN
1490     zdelta = MAX(0., SIGN(1., rtt-zx_t))
1491 guez 47 zx_qs = r2es * FOEEW(zx_t, zdelta)/play(i, k)
1492     zx_qs = MIN(0.5, zx_qs)
1493     zcor = 1./(1.-retv*zx_qs)
1494     zx_qs = zx_qs*zcor
1495 guez 3 ELSE
1496 guez 7 IF (zx_t < t_coup) THEN
1497 guez 47 zx_qs = qsats(zx_t)/play(i, k)
1498 guez 3 ELSE
1499 guez 47 zx_qs = qsatl(zx_t)/play(i, k)
1500 guez 3 ENDIF
1501     ENDIF
1502     zx_rh(i, k) = q_seri(i, k)/zx_qs
1503 guez 51 zqsat(i, k) = zx_qs
1504 guez 3 ENDDO
1505     ENDDO
1506 guez 52
1507     ! Introduce the aerosol direct and first indirect radiative forcings:
1508     ! Johannes Quaas, 27/11/2003 (quaas@lmd.jussieu.fr)
1509     IF (ok_ade .OR. ok_aie) THEN
1510 guez 3 ! Get sulfate aerosol distribution
1511 guez 7 CALL readsulfate(rdayvrai, firstcal, sulfate)
1512     CALL readsulfate_preind(rdayvrai, firstcal, sulfate_pi)
1513 guez 3
1514     ! Calculate aerosol optical properties (Olivier Boucher)
1515 guez 52 CALL aeropt(play, paprs, t_seri, sulfate, rhcl, tau_ae, piz_ae, cg_ae, &
1516     aerindex)
1517 guez 3 ELSE
1518 guez 52 tau_ae = 0.
1519     piz_ae = 0.
1520     cg_ae = 0.
1521 guez 3 ENDIF
1522    
1523 guez 52 ! Paramètres optiques des nuages et quelques paramètres pour
1524     ! diagnostics :
1525 guez 3 if (ok_newmicro) then
1526 guez 52 CALL newmicro(paprs, play, ok_newmicro, t_seri, cldliq, cldfra, &
1527     cldtau, cldemi, cldh, cldl, cldm, cldt, cldq, flwp, fiwp, flwc, &
1528     fiwc, ok_aie, sulfate, sulfate_pi, bl95_b0, bl95_b1, cldtaupi, &
1529     re, fl)
1530 guez 3 else
1531 guez 52 CALL nuage(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, cldh, &
1532     cldl, cldm, cldt, cldq, ok_aie, sulfate, sulfate_pi, bl95_b0, &
1533     bl95_b1, cldtaupi, re, fl)
1534 guez 3 endif
1535    
1536     ! Appeler le rayonnement mais calculer tout d'abord l'albedo du sol.
1537     IF (MOD(itaprad, radpas) == 0) THEN
1538     DO i = 1, klon
1539     albsol(i) = falbe(i, is_oce) * pctsrf(i, is_oce) &
1540     + falbe(i, is_lic) * pctsrf(i, is_lic) &
1541     + falbe(i, is_ter) * pctsrf(i, is_ter) &
1542     + falbe(i, is_sic) * pctsrf(i, is_sic)
1543     albsollw(i) = falblw(i, is_oce) * pctsrf(i, is_oce) &
1544     + falblw(i, is_lic) * pctsrf(i, is_lic) &
1545     + falblw(i, is_ter) * pctsrf(i, is_ter) &
1546     + falblw(i, is_sic) * pctsrf(i, is_sic)
1547     ENDDO
1548     ! nouveau rayonnement (compatible Arpege-IFS):
1549 guez 47 CALL radlwsw(dist, rmu0, fract, paprs, play, zxtsol, albsol, &
1550     albsollw, t_seri, q_seri, wo, cldfra, cldemi, cldtau, heat, &
1551     heat0, cool, cool0, radsol, albpla, topsw, toplw, solsw, sollw, &
1552     sollwdown, topsw0, toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, &
1553     lwup, swdn0, swdn, swup0, swup, ok_ade, ok_aie, tau_ae, piz_ae, &
1554     cg_ae, topswad, solswad, cldtaupi, topswai, solswai)
1555 guez 3 itaprad = 0
1556     ENDIF
1557     itaprad = itaprad + 1
1558    
1559     ! Ajouter la tendance des rayonnements (tous les pas)
1560    
1561     DO k = 1, llm
1562     DO i = 1, klon
1563 guez 52 t_seri(i, k) = t_seri(i, k) + (heat(i, k)-cool(i, k)) * dtphys/86400.
1564 guez 3 ENDDO
1565     ENDDO
1566    
1567     IF (if_ebil >= 2) THEN
1568 guez 51 ztit = 'after rad'
1569 guez 47 CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1570     ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1571     d_ql, d_qs, d_ec)
1572     call diagphy(airephy, ztit, ip_ebil, topsw, toplw, solsw, sollw, &
1573     zero_v, zero_v, zero_v, zero_v, ztsol, d_h_vcol, d_qt, d_ec, &
1574 guez 49 fs_bound, fq_bound)
1575 guez 3 END IF
1576    
1577     ! Calculer l'hydrologie de la surface
1578     DO i = 1, klon
1579     zxqsurf(i) = 0.0
1580     zxsnow(i) = 0.0
1581     ENDDO
1582     DO nsrf = 1, nbsrf
1583     DO i = 1, klon
1584     zxqsurf(i) = zxqsurf(i) + fqsurf(i, nsrf)*pctsrf(i, nsrf)
1585     zxsnow(i) = zxsnow(i) + fsnow(i, nsrf)*pctsrf(i, nsrf)
1586     ENDDO
1587     ENDDO
1588    
1589 guez 51 ! Calculer le bilan du sol et la dérive de température (couplage)
1590 guez 3
1591     DO i = 1, klon
1592     bils(i) = radsol(i) - sens(i) + zxfluxlat(i)
1593     ENDDO
1594    
1595 guez 51 ! Paramétrisation de l'orographie à l'échelle sous-maille :
1596 guez 3
1597     IF (ok_orodr) THEN
1598 guez 47 ! selection des points pour lesquels le shema est actif:
1599 guez 51 igwd = 0
1600     DO i = 1, klon
1601     itest(i) = 0
1602     IF (((zpic(i)-zmea(i)) > 100.).AND.(zstd(i) > 10.0)) THEN
1603     itest(i) = 1
1604     igwd = igwd + 1
1605     idx(igwd) = i
1606 guez 3 ENDIF
1607     ENDDO
1608    
1609 guez 51 CALL drag_noro(klon, llm, dtphys, paprs, play, zmea, zstd, zsig, zgam, &
1610     zthe, zpic, zval, igwd, idx, itest, t_seri, u_seri, v_seri, &
1611     zulow, zvlow, zustrdr, zvstrdr, d_t_oro, d_u_oro, d_v_oro)
1612 guez 3
1613 guez 47 ! ajout des tendances
1614 guez 3 DO k = 1, llm
1615     DO i = 1, klon
1616     t_seri(i, k) = t_seri(i, k) + d_t_oro(i, k)
1617     u_seri(i, k) = u_seri(i, k) + d_u_oro(i, k)
1618     v_seri(i, k) = v_seri(i, k) + d_v_oro(i, k)
1619     ENDDO
1620     ENDDO
1621 guez 13 ENDIF
1622 guez 3
1623     IF (ok_orolf) THEN
1624 guez 51 ! Sélection des points pour lesquels le schéma est actif :
1625     igwd = 0
1626     DO i = 1, klon
1627     itest(i) = 0
1628     IF ((zpic(i) - zmea(i)) > 100.) THEN
1629     itest(i) = 1
1630     igwd = igwd + 1
1631     idx(igwd) = i
1632 guez 3 ENDIF
1633     ENDDO
1634    
1635 guez 47 CALL lift_noro(klon, llm, dtphys, paprs, play, rlat, zmea, zstd, zpic, &
1636     itest, t_seri, u_seri, v_seri, zulow, zvlow, zustrli, zvstrli, &
1637 guez 3 d_t_lif, d_u_lif, d_v_lif)
1638    
1639 guez 51 ! Ajout des tendances :
1640 guez 3 DO k = 1, llm
1641     DO i = 1, klon
1642     t_seri(i, k) = t_seri(i, k) + d_t_lif(i, k)
1643     u_seri(i, k) = u_seri(i, k) + d_u_lif(i, k)
1644     v_seri(i, k) = v_seri(i, k) + d_v_lif(i, k)
1645     ENDDO
1646     ENDDO
1647 guez 49 ENDIF
1648 guez 3
1649     ! STRESS NECESSAIRES: TOUTE LA PHYSIQUE
1650    
1651     DO i = 1, klon
1652 guez 51 zustrph(i) = 0.
1653     zvstrph(i) = 0.
1654 guez 3 ENDDO
1655     DO k = 1, llm
1656     DO i = 1, klon
1657 guez 51 zustrph(i) = zustrph(i) + (u_seri(i, k)-u(i, k))/dtphys* zmasse(i, k)
1658     zvstrph(i) = zvstrph(i) + (v_seri(i, k)-v(i, k))/dtphys* zmasse(i, k)
1659 guez 3 ENDDO
1660     ENDDO
1661    
1662 guez 56 CALL aaam_bud(ra, rg, romega, rlat, rlon, pphis, zustrdr, zustrli, &
1663     zustrph, zvstrdr, zvstrli, zvstrph, paprs, u, v, aam, torsfc)
1664 guez 3
1665     IF (if_ebil >= 2) THEN
1666 guez 51 ztit = 'after orography'
1667 guez 47 CALL diagetpq(airephy, ztit, ip_ebil, 2, 2, dtphys, t_seri, q_seri, &
1668     ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1669     d_ql, d_qs, d_ec)
1670 guez 3 END IF
1671    
1672 guez 47 ! Calcul des tendances traceurs
1673     call phytrac(rnpb, itap, lmt_pas, julien, time, firstcal, lafin, &
1674     nqmx-2, dtphys, u, t, paprs, play, pmfu, pmfd, pen_u, pde_u, &
1675 guez 35 pen_d, pde_d, ycoefh, fm_therm, entr_therm, yu1, yv1, ftsol, pctsrf, &
1676 guez 47 frac_impa, frac_nucl, pphis, albsol, rhcl, cldfra, rneb, &
1677 guez 34 diafra, cldliq, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, &
1678     tr_seri, zmasse)
1679 guez 3
1680     IF (offline) THEN
1681 guez 47 call phystokenc(dtphys, rlon, rlat, t, pmfu, pmfd, pen_u, pde_u, &
1682 guez 31 pen_d, pde_d, fm_therm, entr_therm, ycoefh, yu1, yv1, ftsol, &
1683 guez 47 pctsrf, frac_impa, frac_nucl, pphis, airephy, dtphys, itap)
1684 guez 3 ENDIF
1685    
1686     ! Calculer le transport de l'eau et de l'energie (diagnostique)
1687 guez 31 CALL transp(paprs, zxtsol, t_seri, q_seri, u_seri, v_seri, zphi, ve, vq, &
1688     ue, uq)
1689 guez 3
1690 guez 31 ! diag. bilKP
1691 guez 3
1692 guez 52 CALL transp_lay(paprs, zxtsol, t_seri, q_seri, u_seri, v_seri, zphi, &
1693 guez 3 ve_lay, vq_lay, ue_lay, uq_lay)
1694    
1695     ! Accumuler les variables a stocker dans les fichiers histoire:
1696    
1697 guez 51 ! conversion Ec -> E thermique
1698 guez 3 DO k = 1, llm
1699     DO i = 1, klon
1700 guez 51 ZRCPD = RCPD * (1. + RVTMP2 * q_seri(i, k))
1701     d_t_ec(i, k) = 0.5 / ZRCPD &
1702     * (u(i, k)**2 + v(i, k)**2 - u_seri(i, k)**2 - v_seri(i, k)**2)
1703     t_seri(i, k) = t_seri(i, k) + d_t_ec(i, k)
1704     d_t_ec(i, k) = d_t_ec(i, k) / dtphys
1705 guez 3 END DO
1706     END DO
1707 guez 51
1708 guez 3 IF (if_ebil >= 1) THEN
1709 guez 51 ztit = 'after physic'
1710 guez 47 CALL diagetpq(airephy, ztit, ip_ebil, 1, 1, dtphys, t_seri, q_seri, &
1711     ql_seri, qs_seri, u_seri, v_seri, paprs, d_h_vcol, d_qt, d_qw, &
1712     d_ql, d_qs, d_ec)
1713     ! Comme les tendances de la physique sont ajoute dans la dynamique,
1714     ! on devrait avoir que la variation d'entalpie par la dynamique
1715     ! est egale a la variation de la physique au pas de temps precedent.
1716     ! Donc la somme de ces 2 variations devrait etre nulle.
1717     call diagphy(airephy, ztit, ip_ebil, topsw, toplw, solsw, sollw, sens, &
1718     evap, rain_fall, snow_fall, ztsol, d_h_vcol, d_qt, d_ec, &
1719 guez 49 fs_bound, fq_bound)
1720 guez 3
1721 guez 51 d_h_vcol_phy = d_h_vcol
1722 guez 3
1723     END IF
1724    
1725 guez 47 ! SORTIES
1726 guez 3
1727     !cc prw = eau precipitable
1728     DO i = 1, klon
1729     prw(i) = 0.
1730     DO k = 1, llm
1731 guez 17 prw(i) = prw(i) + q_seri(i, k)*zmasse(i, k)
1732 guez 3 ENDDO
1733     ENDDO
1734    
1735     ! Convertir les incrementations en tendances
1736    
1737     DO k = 1, llm
1738     DO i = 1, klon
1739 guez 49 d_u(i, k) = (u_seri(i, k) - u(i, k)) / dtphys
1740     d_v(i, k) = (v_seri(i, k) - v(i, k)) / dtphys
1741     d_t(i, k) = (t_seri(i, k) - t(i, k)) / dtphys
1742     d_qx(i, k, ivap) = (q_seri(i, k) - qx(i, k, ivap)) / dtphys
1743     d_qx(i, k, iliq) = (ql_seri(i, k) - qx(i, k, iliq)) / dtphys
1744 guez 3 ENDDO
1745     ENDDO
1746    
1747 guez 34 IF (nqmx >= 3) THEN
1748     DO iq = 3, nqmx
1749 guez 47 DO k = 1, llm
1750     DO i = 1, klon
1751     d_qx(i, k, iq) = (tr_seri(i, k, iq-2) - qx(i, k, iq)) / dtphys
1752 guez 3 ENDDO
1753     ENDDO
1754     ENDDO
1755     ENDIF
1756    
1757     ! Sauvegarder les valeurs de t et q a la fin de la physique:
1758     DO k = 1, llm
1759     DO i = 1, klon
1760     t_ancien(i, k) = t_seri(i, k)
1761     q_ancien(i, k) = q_seri(i, k)
1762     ENDDO
1763     ENDDO
1764    
1765 guez 47 ! Ecriture des sorties
1766 guez 3 call write_histhf
1767     call write_histday
1768     call write_histins
1769    
1770     ! Si c'est la fin, il faut conserver l'etat de redemarrage
1771     IF (lafin) THEN
1772     itau_phy = itau_phy + itap
1773 guez 49 CALL phyredem("restartphy.nc", rlat, rlon, pctsrf, ftsol, ftsoil, &
1774     tslab, seaice, fqsurf, qsol, fsnow, falbe, falblw, fevap, &
1775     rain_fall, snow_fall, solsw, sollwdown, dlw, radsol, frugs, &
1776     agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
1777     q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0)
1778 guez 3 ENDIF
1779    
1780 guez 35 firstcal = .FALSE.
1781    
1782 guez 3 contains
1783    
1784 guez 15 subroutine write_histday
1785 guez 3
1786 guez 32 use gr_phy_write_3d_m, only: gr_phy_write_3d
1787 guez 47 integer itau_w ! pas de temps ecriture
1788 guez 3
1789 guez 15 !------------------------------------------------
1790 guez 3
1791     if (ok_journe) THEN
1792     itau_w = itau_phy + itap
1793 guez 34 if (nqmx <= 4) then
1794 guez 17 call histwrite(nid_day, "Sigma_O3_Royer", itau_w, &
1795     gr_phy_write_3d(wo) * 1e3)
1796     ! (convert "wo" from kDU to DU)
1797     end if
1798 guez 3 if (ok_sync) then
1799     call histsync(nid_day)
1800     endif
1801     ENDIF
1802    
1803     End subroutine write_histday
1804    
1805     !****************************
1806    
1807     subroutine write_histhf
1808    
1809 guez 47 ! From phylmd/write_histhf.h, version 1.5 2005/05/25 13:10:09
1810 guez 3
1811 guez 17 !------------------------------------------------
1812 guez 3
1813     call write_histhf3d
1814    
1815     IF (ok_sync) THEN
1816     call histsync(nid_hf)
1817     ENDIF
1818    
1819     end subroutine write_histhf
1820    
1821     !***************************************************************
1822    
1823     subroutine write_histins
1824    
1825 guez 47 ! From phylmd/write_histins.h, version 1.2 2005/05/25 13:10:09
1826 guez 3
1827     real zout
1828 guez 47 integer itau_w ! pas de temps ecriture
1829 guez 3
1830     !--------------------------------------------------
1831    
1832     IF (ok_instan) THEN
1833     ! Champs 2D:
1834    
1835 guez 47 zsto = dtphys * ecrit_ins
1836     zout = dtphys * ecrit_ins
1837 guez 3 itau_w = itau_phy + itap
1838    
1839     i = NINT(zout/zsto)
1840 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, pphis, zx_tmp_2d)
1841 guez 15 CALL histwrite(nid_ins, "phis", itau_w, zx_tmp_2d)
1842 guez 3
1843     i = NINT(zout/zsto)
1844 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, airephy, zx_tmp_2d)
1845 guez 15 CALL histwrite(nid_ins, "aire", itau_w, zx_tmp_2d)
1846 guez 3
1847     DO i = 1, klon
1848     zx_tmp_fi2d(i) = paprs(i, 1)
1849     ENDDO
1850 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1851 guez 15 CALL histwrite(nid_ins, "psol", itau_w, zx_tmp_2d)
1852 guez 3
1853     DO i = 1, klon
1854     zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i)
1855     ENDDO
1856 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1857 guez 15 CALL histwrite(nid_ins, "precip", itau_w, zx_tmp_2d)
1858 guez 3
1859     DO i = 1, klon
1860     zx_tmp_fi2d(i) = rain_lsc(i) + snow_lsc(i)
1861     ENDDO
1862 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1863 guez 15 CALL histwrite(nid_ins, "plul", itau_w, zx_tmp_2d)
1864 guez 3
1865     DO i = 1, klon
1866     zx_tmp_fi2d(i) = rain_con(i) + snow_con(i)
1867     ENDDO
1868 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1869 guez 15 CALL histwrite(nid_ins, "pluc", itau_w, zx_tmp_2d)
1870 guez 3
1871 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zxtsol, zx_tmp_2d)
1872 guez 15 CALL histwrite(nid_ins, "tsol", itau_w, zx_tmp_2d)
1873 guez 3 !ccIM
1874 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zt2m, zx_tmp_2d)
1875 guez 15 CALL histwrite(nid_ins, "t2m", itau_w, zx_tmp_2d)
1876 guez 3
1877 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zq2m, zx_tmp_2d)
1878 guez 15 CALL histwrite(nid_ins, "q2m", itau_w, zx_tmp_2d)
1879 guez 3
1880 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zu10m, zx_tmp_2d)
1881 guez 15 CALL histwrite(nid_ins, "u10m", itau_w, zx_tmp_2d)
1882 guez 3
1883 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zv10m, zx_tmp_2d)
1884 guez 15 CALL histwrite(nid_ins, "v10m", itau_w, zx_tmp_2d)
1885 guez 3
1886 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, snow_fall, zx_tmp_2d)
1887 guez 15 CALL histwrite(nid_ins, "snow", itau_w, zx_tmp_2d)
1888 guez 3
1889 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, cdragm, zx_tmp_2d)
1890 guez 15 CALL histwrite(nid_ins, "cdrm", itau_w, zx_tmp_2d)
1891 guez 3
1892 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, cdragh, zx_tmp_2d)
1893 guez 15 CALL histwrite(nid_ins, "cdrh", itau_w, zx_tmp_2d)
1894 guez 3
1895 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, toplw, zx_tmp_2d)
1896 guez 15 CALL histwrite(nid_ins, "topl", itau_w, zx_tmp_2d)
1897 guez 3
1898 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, evap, zx_tmp_2d)
1899 guez 15 CALL histwrite(nid_ins, "evap", itau_w, zx_tmp_2d)
1900 guez 3
1901 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, solsw, zx_tmp_2d)
1902 guez 15 CALL histwrite(nid_ins, "sols", itau_w, zx_tmp_2d)
1903 guez 3
1904 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, sollw, zx_tmp_2d)
1905 guez 15 CALL histwrite(nid_ins, "soll", itau_w, zx_tmp_2d)
1906 guez 3
1907 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, sollwdown, zx_tmp_2d)
1908 guez 15 CALL histwrite(nid_ins, "solldown", itau_w, zx_tmp_2d)
1909 guez 3
1910 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, bils, zx_tmp_2d)
1911 guez 15 CALL histwrite(nid_ins, "bils", itau_w, zx_tmp_2d)
1912 guez 3
1913 guez 51 zx_tmp_fi2d(1:klon) = -1*sens(1:klon)
1914 guez 52 ! CALL gr_fi_ecrit(1, klon, iim, jjm + 1, sens, zx_tmp_2d)
1915     CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1916 guez 15 CALL histwrite(nid_ins, "sens", itau_w, zx_tmp_2d)
1917 guez 3
1918 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, fder, zx_tmp_2d)
1919 guez 15 CALL histwrite(nid_ins, "fder", itau_w, zx_tmp_2d)
1920 guez 3
1921 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, d_ts(1, is_oce), zx_tmp_2d)
1922 guez 15 CALL histwrite(nid_ins, "dtsvdfo", itau_w, zx_tmp_2d)
1923 guez 3
1924 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, d_ts(1, is_ter), zx_tmp_2d)
1925 guez 15 CALL histwrite(nid_ins, "dtsvdft", itau_w, zx_tmp_2d)
1926 guez 3
1927 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, d_ts(1, is_lic), zx_tmp_2d)
1928 guez 15 CALL histwrite(nid_ins, "dtsvdfg", itau_w, zx_tmp_2d)
1929 guez 3
1930 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, d_ts(1, is_sic), zx_tmp_2d)
1931 guez 15 CALL histwrite(nid_ins, "dtsvdfi", itau_w, zx_tmp_2d)
1932 guez 3
1933     DO nsrf = 1, nbsrf
1934     !XXX
1935 guez 49 zx_tmp_fi2d(1 : klon) = pctsrf(1 : klon, nsrf)*100.
1936 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1937 guez 3 CALL histwrite(nid_ins, "pourc_"//clnsurf(nsrf), itau_w, &
1938 guez 15 zx_tmp_2d)
1939 guez 3
1940 guez 49 zx_tmp_fi2d(1 : klon) = pctsrf(1 : klon, nsrf)
1941 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1942 guez 3 CALL histwrite(nid_ins, "fract_"//clnsurf(nsrf), itau_w, &
1943 guez 15 zx_tmp_2d)
1944 guez 3
1945 guez 49 zx_tmp_fi2d(1 : klon) = fluxt(1 : klon, 1, nsrf)
1946 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1947 guez 3 CALL histwrite(nid_ins, "sens_"//clnsurf(nsrf), itau_w, &
1948 guez 15 zx_tmp_2d)
1949 guez 3
1950 guez 49 zx_tmp_fi2d(1 : klon) = fluxlat(1 : klon, nsrf)
1951 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1952 guez 3 CALL histwrite(nid_ins, "lat_"//clnsurf(nsrf), itau_w, &
1953 guez 15 zx_tmp_2d)
1954 guez 3
1955 guez 49 zx_tmp_fi2d(1 : klon) = ftsol(1 : klon, nsrf)
1956 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1957 guez 3 CALL histwrite(nid_ins, "tsol_"//clnsurf(nsrf), itau_w, &
1958 guez 15 zx_tmp_2d)
1959 guez 3
1960 guez 49 zx_tmp_fi2d(1 : klon) = fluxu(1 : klon, 1, nsrf)
1961 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1962 guez 3 CALL histwrite(nid_ins, "taux_"//clnsurf(nsrf), itau_w, &
1963 guez 15 zx_tmp_2d)
1964 guez 3
1965 guez 49 zx_tmp_fi2d(1 : klon) = fluxv(1 : klon, 1, nsrf)
1966 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1967 guez 3 CALL histwrite(nid_ins, "tauy_"//clnsurf(nsrf), itau_w, &
1968 guez 15 zx_tmp_2d)
1969 guez 3
1970 guez 49 zx_tmp_fi2d(1 : klon) = frugs(1 : klon, nsrf)
1971 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1972 guez 3 CALL histwrite(nid_ins, "rugs_"//clnsurf(nsrf), itau_w, &
1973 guez 15 zx_tmp_2d)
1974 guez 3
1975 guez 49 zx_tmp_fi2d(1 : klon) = falbe(1 : klon, nsrf)
1976 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zx_tmp_fi2d, zx_tmp_2d)
1977 guez 3 CALL histwrite(nid_ins, "albe_"//clnsurf(nsrf), itau_w, &
1978 guez 15 zx_tmp_2d)
1979 guez 3
1980     END DO
1981 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, albsol, zx_tmp_2d)
1982 guez 15 CALL histwrite(nid_ins, "albs", itau_w, zx_tmp_2d)
1983 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, albsollw, zx_tmp_2d)
1984 guez 15 CALL histwrite(nid_ins, "albslw", itau_w, zx_tmp_2d)
1985 guez 3
1986 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, zxrugs, zx_tmp_2d)
1987 guez 15 CALL histwrite(nid_ins, "rugs", itau_w, zx_tmp_2d)
1988 guez 3
1989     !HBTM2
1990    
1991 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, s_pblh, zx_tmp_2d)
1992 guez 15 CALL histwrite(nid_ins, "s_pblh", itau_w, zx_tmp_2d)
1993 guez 3
1994 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, s_pblt, zx_tmp_2d)
1995 guez 15 CALL histwrite(nid_ins, "s_pblt", itau_w, zx_tmp_2d)
1996 guez 3
1997 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, s_lcl, zx_tmp_2d)
1998 guez 15 CALL histwrite(nid_ins, "s_lcl", itau_w, zx_tmp_2d)
1999 guez 3
2000 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, s_capCL, zx_tmp_2d)
2001 guez 15 CALL histwrite(nid_ins, "s_capCL", itau_w, zx_tmp_2d)
2002 guez 3
2003 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, s_oliqCL, zx_tmp_2d)
2004 guez 15 CALL histwrite(nid_ins, "s_oliqCL", itau_w, zx_tmp_2d)
2005 guez 3
2006 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, s_cteiCL, zx_tmp_2d)
2007 guez 15 CALL histwrite(nid_ins, "s_cteiCL", itau_w, zx_tmp_2d)
2008 guez 3
2009 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, s_therm, zx_tmp_2d)
2010 guez 15 CALL histwrite(nid_ins, "s_therm", itau_w, zx_tmp_2d)
2011 guez 3
2012 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, s_trmb1, zx_tmp_2d)
2013 guez 15 CALL histwrite(nid_ins, "s_trmb1", itau_w, zx_tmp_2d)
2014 guez 3
2015 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, s_trmb2, zx_tmp_2d)
2016 guez 15 CALL histwrite(nid_ins, "s_trmb2", itau_w, zx_tmp_2d)
2017 guez 3
2018 guez 52 CALL gr_fi_ecrit(1, klon, iim, jjm + 1, s_trmb3, zx_tmp_2d)
2019 guez 15 CALL histwrite(nid_ins, "s_trmb3", itau_w, zx_tmp_2d)
2020 guez 3
2021     ! Champs 3D:
2022    
2023 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, t_seri, zx_tmp_3d)
2024 guez 15 CALL histwrite(nid_ins, "temp", itau_w, zx_tmp_3d)
2025 guez 3
2026 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, u_seri, zx_tmp_3d)
2027 guez 15 CALL histwrite(nid_ins, "vitu", itau_w, zx_tmp_3d)
2028 guez 3
2029 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, v_seri, zx_tmp_3d)
2030 guez 15 CALL histwrite(nid_ins, "vitv", itau_w, zx_tmp_3d)
2031 guez 3
2032 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, zphi, zx_tmp_3d)
2033 guez 15 CALL histwrite(nid_ins, "geop", itau_w, zx_tmp_3d)
2034 guez 3
2035 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, play, zx_tmp_3d)
2036 guez 15 CALL histwrite(nid_ins, "pres", itau_w, zx_tmp_3d)
2037 guez 3
2038 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, d_t_vdf, zx_tmp_3d)
2039 guez 15 CALL histwrite(nid_ins, "dtvdf", itau_w, zx_tmp_3d)
2040 guez 3
2041 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, d_q_vdf, zx_tmp_3d)
2042 guez 15 CALL histwrite(nid_ins, "dqvdf", itau_w, zx_tmp_3d)
2043 guez 3
2044     if (ok_sync) then
2045     call histsync(nid_ins)
2046     endif
2047     ENDIF
2048    
2049     end subroutine write_histins
2050    
2051     !****************************************************
2052    
2053     subroutine write_histhf3d
2054    
2055 guez 47 ! From phylmd/write_histhf3d.h, version 1.2 2005/05/25 13:10:09
2056 guez 3
2057 guez 47 integer itau_w ! pas de temps ecriture
2058 guez 3
2059 guez 17 !-------------------------------------------------------
2060    
2061 guez 3 itau_w = itau_phy + itap
2062    
2063     ! Champs 3D:
2064    
2065 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, t_seri, zx_tmp_3d)
2066 guez 15 CALL histwrite(nid_hf3d, "temp", itau_w, zx_tmp_3d)
2067 guez 3
2068 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, qx(1, 1, ivap), zx_tmp_3d)
2069 guez 15 CALL histwrite(nid_hf3d, "ovap", itau_w, zx_tmp_3d)
2070 guez 3
2071 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, u_seri, zx_tmp_3d)
2072 guez 15 CALL histwrite(nid_hf3d, "vitu", itau_w, zx_tmp_3d)
2073 guez 3
2074 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, v_seri, zx_tmp_3d)
2075 guez 15 CALL histwrite(nid_hf3d, "vitv", itau_w, zx_tmp_3d)
2076 guez 3
2077 guez 6 if (nbtr >= 3) then
2078 guez 52 CALL gr_fi_ecrit(llm, klon, iim, jjm + 1, tr_seri(1, 1, 3), &
2079 guez 6 zx_tmp_3d)
2080 guez 15 CALL histwrite(nid_hf3d, "O3", itau_w, zx_tmp_3d)
2081 guez 6 end if
2082 guez 3
2083     if (ok_sync) then
2084     call histsync(nid_hf3d)
2085     endif
2086    
2087     end subroutine write_histhf3d
2088    
2089     END SUBROUTINE physiq
2090    
2091     end module physiq_m

  ViewVC Help
Powered by ViewVC 1.1.21