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

Diff of /trunk/phylmd/physiq.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/Sources/phylmd/physiq.f revision 212 by guez, Thu Jan 12 12:31:31 2017 UTC trunk/phylmd/physiq.f revision 307 by guez, Tue Sep 11 12:52:28 2018 UTC
# Line 18  contains Line 18  contains
18      USE abort_gcm_m, ONLY: abort_gcm      USE abort_gcm_m, ONLY: abort_gcm
19      use ajsec_m, only: ajsec      use ajsec_m, only: ajsec
20      use calltherm_m, only: calltherm      use calltherm_m, only: calltherm
21      USE clesphys, ONLY: cdhmax, cdmmax, ecrit_ins, ksta, ksta_ter, ok_kzmin, &      USE clesphys, ONLY: cdhmax, cdmmax, ecrit_ins, ok_instan
          ok_instan  
22      USE clesphys2, ONLY: conv_emanuel, nbapp_rad, new_oliq, ok_orodr, ok_orolf      USE clesphys2, ONLY: conv_emanuel, nbapp_rad, new_oliq, ok_orodr, ok_orolf
23      USE clmain_m, ONLY: clmain      USE conf_interface_m, ONLY: conf_interface
24        USE pbl_surface_m, ONLY: pbl_surface
25      use clouds_gno_m, only: clouds_gno      use clouds_gno_m, only: clouds_gno
26      use comconst, only: dtphys      use comconst, only: dtphys
27      USE comgeomphy, ONLY: airephy      USE comgeomphy, ONLY: airephy
28      USE concvl_m, ONLY: concvl      USE concvl_m, ONLY: concvl
29      USE conf_gcm_m, ONLY: offline, lmt_pas      USE conf_gcm_m, ONLY: lmt_pas
30      USE conf_phys_m, ONLY: conf_phys      USE conf_phys_m, ONLY: conf_phys
31      use conflx_m, only: conflx      use conflx_m, only: conflx
32      USE ctherm, ONLY: iflag_thermals, nsplit_thermals      USE ctherm, ONLY: iflag_thermals, nsplit_thermals
33      use diagcld2_m, only: diagcld2      use diagcld2_m, only: diagcld2
34      USE dimens_m, ONLY: llm, nqmx      USE dimensions, ONLY: llm, nqmx
35      USE dimphy, ONLY: klon      USE dimphy, ONLY: klon
36      USE dimsoil, ONLY: nsoilmx      USE dimsoil, ONLY: nsoilmx
37      use drag_noro_m, only: drag_noro      use drag_noro_m, only: drag_noro
38      use dynetat0_m, only: day_ref, annee_ref      use dynetat0_m, only: day_ref, annee_ref
39      USE fcttre, ONLY: foeew, qsatl, qsats      USE fcttre, ONLY: foeew
40      use fisrtilp_m, only: fisrtilp      use fisrtilp_m, only: fisrtilp
41      USE hgardfou_m, ONLY: hgardfou      USE hgardfou_m, ONLY: hgardfou
42      USE histsync_m, ONLY: histsync      USE histsync_m, ONLY: histsync
# Line 44  contains Line 44  contains
44      USE indicesol, ONLY: clnsurf, epsfra, is_lic, is_oce, is_sic, is_ter, &      USE indicesol, ONLY: clnsurf, epsfra, is_lic, is_oce, is_sic, is_ter, &
45           nbsrf           nbsrf
46      USE ini_histins_m, ONLY: ini_histins, nid_ins      USE ini_histins_m, ONLY: ini_histins, nid_ins
47        use lift_noro_m, only: lift_noro
48      use netcdf95, only: NF95_CLOSE      use netcdf95, only: NF95_CLOSE
49      use newmicro_m, only: newmicro      use newmicro_m, only: newmicro
50      use nr_util, only: assert      use nr_util, only: assert
51      use nuage_m, only: nuage      use nuage_m, only: nuage
52      USE orbite_m, ONLY: orbite      USE orbite_m, ONLY: orbite
53      USE ozonecm_m, ONLY: ozonecm      USE ozonecm_m, ONLY: ozonecm
54      USE phyetat0_m, ONLY: phyetat0, rlat, rlon      USE phyetat0_m, ONLY: phyetat0
55      USE phyredem_m, ONLY: phyredem      USE phyredem_m, ONLY: phyredem
56      USE phyredem0_m, ONLY: phyredem0      USE phyredem0_m, ONLY: phyredem0
     USE phystokenc_m, ONLY: phystokenc  
57      USE phytrac_m, ONLY: phytrac      USE phytrac_m, ONLY: phytrac
58      use radlwsw_m, only: radlwsw      use radlwsw_m, only: radlwsw
59      use yoegwd, only: sugwd      use yoegwd, only: sugwd
# Line 150  contains Line 150  contains
150      REAL, save:: ftsoil(klon, nsoilmx, nbsrf)      REAL, save:: ftsoil(klon, nsoilmx, nbsrf)
151      ! soil temperature of surface fraction      ! soil temperature of surface fraction
152    
153      REAL, save:: fevap(klon, nbsrf) ! evaporation      REAL fluxlat(klon, nbsrf)
     REAL, save:: fluxlat(klon, nbsrf)  
154    
155      REAL, save:: fqsurf(klon, nbsrf)      REAL, save:: fqsurf(klon, nbsrf)
156      ! humidite de l'air au contact de la surface      ! humidite de l'air au contact de la surface
157    
158      REAL, save:: qsol(klon)      REAL, save:: qsol(klon) ! column-density of water in soil, in kg m-2
159      ! column-density of water in soil, in kg m-2      REAL, save:: fsnow(klon, nbsrf) ! \'epaisseur neigeuse
   
     REAL, save:: fsnow(klon, nbsrf) ! epaisseur neigeuse  
160      REAL, save:: falbe(klon, nbsrf) ! albedo visible par type de surface      REAL, save:: falbe(klon, nbsrf) ! albedo visible par type de surface
161    
162      ! Param\`etres de l'orographie \`a l'\'echelle sous-maille (OESM) :      ! Param\`etres de l'orographie \`a l'\'echelle sous-maille (OESM) :
# Line 172  contains Line 169  contains
169      REAL, save:: zval(klon) ! Minimum de l'OESM      REAL, save:: zval(klon) ! Minimum de l'OESM
170      REAL, save:: rugoro(klon) ! longueur de rugosite de l'OESM      REAL, save:: rugoro(klon) ! longueur de rugosite de l'OESM
171      REAL zulow(klon), zvlow(klon)      REAL zulow(klon), zvlow(klon)
172      INTEGER igwd, itest(klon)      INTEGER ktest(klon)
173    
174      REAL, save:: agesno(klon, nbsrf) ! age de la neige      REAL, save:: agesno(klon, nbsrf) ! age de la neige
175      REAL, save:: run_off_lic_0(klon)      REAL, save:: run_off_lic_0(klon)
176    
177      ! Variables li\'ees \`a la convection d'Emanuel :      ! Variables li\'ees \`a la convection d'Emanuel :
178      REAL, save:: Ma(klon, llm) ! undilute upward mass flux      REAL, save:: Ma(klon, llm) ! undilute upward mass flux
     REAL, save:: qcondc(klon, llm) ! in-cld water content from convect  
179      REAL, save:: sig1(klon, llm), w01(klon, llm)      REAL, save:: sig1(klon, llm), w01(klon, llm)
180    
181      ! Variables pour la couche limite (Alain Lahellec) :      ! Variables pour la couche limite (Alain Lahellec) :
182      REAL cdragh(klon) ! drag coefficient pour T and Q      REAL cdragh(klon) ! drag coefficient pour T and Q
183      REAL cdragm(klon) ! drag coefficient pour vent      REAL cdragm(klon) ! drag coefficient pour vent
184    
185      ! Pour phytrac :      REAL coefh(klon, 2:llm) ! coef d'echange pour phytrac
     REAL ycoefh(klon, llm) ! coef d'echange pour phytrac  
     REAL yu1(klon) ! vents dans la premiere couche U  
     REAL yv1(klon) ! vents dans la premiere couche V  
186    
187      REAL, save:: ffonte(klon, nbsrf)      REAL, save:: ffonte(klon, nbsrf)
188      ! flux thermique utilise pour fondre la neige      ! flux thermique utilise pour fondre la neige
189    
190      REAL, save:: fqcalving(klon, nbsrf)      REAL fqcalving(klon, nbsrf)
191      ! flux d'eau "perdue" par la surface et necessaire pour limiter la      ! flux d'eau "perdue" par la surface et n\'ecessaire pour limiter
192      ! hauteur de neige, en kg / m2 / s      ! la hauteur de neige, en kg / m2 / s
193    
194      REAL zxffonte(klon), zxfqcalving(klon)      REAL zxffonte(klon)
195    
196      REAL, save:: pfrac_impa(klon, llm)! Produits des coefs lessivage impaction      REAL, save:: pfrac_impa(klon, llm)! Produits des coefs lessivage impaction
197      REAL, save:: pfrac_nucl(klon, llm)! Produits des coefs lessivage nucleation      REAL, save:: pfrac_nucl(klon, llm)! Produits des coefs lessivage nucleation
# Line 206  contains Line 199  contains
199      REAL, save:: pfrac_1nucl(klon, llm)      REAL, save:: pfrac_1nucl(klon, llm)
200      ! Produits des coefs lessi nucl (alpha = 1)      ! Produits des coefs lessi nucl (alpha = 1)
201    
202      REAL frac_impa(klon, llm) ! fractions d'aerosols lessivees (impaction)      REAL frac_impa(klon, llm) ! fraction d'a\'erosols lessiv\'es (impaction)
203      REAL frac_nucl(klon, llm) ! idem (nucleation)      REAL frac_nucl(klon, llm) ! idem (nucleation)
204    
205      REAL, save:: rain_fall(klon)      REAL, save:: rain_fall(klon)
# Line 218  contains Line 211  contains
211      REAL rain_tiedtke(klon), snow_tiedtke(klon)      REAL rain_tiedtke(klon), snow_tiedtke(klon)
212    
213      REAL evap(klon) ! flux d'\'evaporation au sol      REAL evap(klon) ! flux d'\'evaporation au sol
214      real devap(klon) ! derivative of the evaporation flux at the surface      real dflux_q(klon) ! derivative of the evaporation flux at the surface
215      REAL sens(klon) ! flux de chaleur sensible au sol      REAL sens(klon) ! flux de chaleur sensible au sol
216      real dsens(klon) ! derivee du flux de chaleur sensible au sol      real dflux_t(klon) ! derivee du flux de chaleur sensible au sol
217      REAL, save:: dlw(klon) ! derivee infra rouge      REAL, save:: dlw(klon) ! derivative of infra-red flux
218      REAL bils(klon) ! bilan de chaleur au sol      REAL bils(klon) ! bilan de chaleur au sol
219      REAL, save:: fder(klon) ! Derive de flux (sensible et latente)      REAL fder(klon) ! Derive de flux (sensible et latente)
220      REAL ve(klon) ! integr. verticale du transport meri. de l'energie      REAL ve(klon) ! integr. verticale du transport meri. de l'energie
221      REAL vq(klon) ! integr. verticale du transport meri. de l'eau      REAL vq(klon) ! integr. verticale du transport meri. de l'eau
222      REAL ue(klon) ! integr. verticale du transport zonal de l'energie      REAL ue(klon) ! integr. verticale du transport zonal de l'energie
# Line 236  contains Line 229  contains
229    
230      INTEGER julien      INTEGER julien
231      REAL, save:: pctsrf(klon, nbsrf) ! percentage of surface      REAL, save:: pctsrf(klon, nbsrf) ! percentage of surface
232      REAL, save:: albsol(klon) ! albedo du sol total visible      REAL, save:: albsol(klon) ! albedo du sol total, visible, moyen par maille
233      REAL, SAVE:: wo(klon, llm) ! column density of ozone in a cell, in kDU      REAL, SAVE:: wo(klon, llm) ! column density of ozone in a cell, in kDU
234      real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2      real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
235    
236      real, save:: clwcon(klon, llm), rnebcon(klon, llm)      real, save:: clwcon(klon, llm), rnebcon(klon, llm)
237      real, save:: clwcon0(klon, llm), rnebcon0(klon, llm)      real, save:: clwcon0(klon, llm), rnebcon0(klon, llm)
238    
239      REAL rhcl(klon, llm) ! humiditi relative ciel clair      REAL rhcl(klon, llm) ! humidit\'e relative ciel clair
240      REAL dialiq(klon, llm) ! eau liquide nuageuse      REAL dialiq(klon, llm) ! eau liquide nuageuse
241      REAL diafra(klon, llm) ! fraction nuageuse      REAL diafra(klon, llm) ! fraction nuageuse
242      REAL cldliq(klon, llm) ! eau liquide nuageuse      REAL cldliq(klon, llm) ! eau liquide nuageuse
# Line 253  contains Line 246  contains
246    
247      REAL flux_q(klon, nbsrf) ! flux turbulent d'humidite à la surface      REAL flux_q(klon, nbsrf) ! flux turbulent d'humidite à la surface
248      REAL flux_t(klon, nbsrf) ! flux turbulent de chaleur à la surface      REAL flux_t(klon, nbsrf) ! flux turbulent de chaleur à la surface
249      REAL flux_u(klon, nbsrf) ! flux turbulent de vitesse u à la surface  
250      REAL flux_v(klon, nbsrf) ! flux turbulent de vitesse v à la surface      REAL flux_u(klon, nbsrf), flux_v(klon, nbsrf)
251        ! tension du vent (flux turbulent de vent) à la surface, en Pa
252    
253      ! Le rayonnement n'est pas calcul\'e tous les pas, il faut donc que      ! Le rayonnement n'est pas calcul\'e tous les pas, il faut donc que
254      ! les variables soient r\'emanentes.      ! les variables soient r\'emanentes.
# Line 267  contains Line 261  contains
261      real, save:: sollwdown(klon) ! downward LW flux at surface      real, save:: sollwdown(klon) ! downward LW flux at surface
262      REAL, save:: topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)      REAL, save:: topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)
263      REAL, save:: albpla(klon)      REAL, save:: albpla(klon)
     REAL fsollw(klon, nbsrf) ! bilan flux IR pour chaque sous-surface  
     REAL fsolsw(klon, nbsrf) ! flux solaire absorb\'e pour chaque sous-surface  
264    
265      REAL conv_q(klon, llm) ! convergence de l'humidite (kg / kg / s)      REAL conv_q(klon, llm) ! convergence de l'humidite (kg / kg / s)
266      REAL conv_t(klon, llm) ! convergence of temperature (K / s)      REAL conv_t(klon, llm) ! convergence of temperature (K / s)
# Line 276  contains Line 268  contains
268      REAL cldl(klon), cldm(klon), cldh(klon) ! nuages bas, moyen et haut      REAL cldl(klon), cldm(klon), cldh(klon) ! nuages bas, moyen et haut
269      REAL cldt(klon), cldq(klon) ! nuage total, eau liquide integree      REAL cldt(klon), cldq(klon) ! nuage total, eau liquide integree
270    
271      REAL zxqsurf(klon), zxsnow(klon), zxfluxlat(klon)      REAL zxfluxlat(klon)
   
272      REAL dist, mu0(klon), fract(klon)      REAL dist, mu0(klon), fract(klon)
273      real longi      real longi
274      REAL z_avant(klon), z_apres(klon), z_factor(klon)      REAL z_avant(klon), z_apres(klon), z_factor(klon)
# Line 296  contains Line 287  contains
287      REAL, SAVE:: cteiCL(klon, nbsrf) ! cloud top instab. crit. couche limite      REAL, SAVE:: cteiCL(klon, nbsrf) ! cloud top instab. crit. couche limite
288      REAL, SAVE:: pblt(klon, nbsrf) ! T \`a la hauteur de couche limite      REAL, SAVE:: pblt(klon, nbsrf) ! T \`a la hauteur de couche limite
289      REAL, SAVE:: therm(klon, nbsrf)      REAL, SAVE:: therm(klon, nbsrf)
     REAL, SAVE:: trmb1(klon, nbsrf) ! deep_cape  
     REAL, SAVE:: trmb2(klon, nbsrf) ! inhibition  
     REAL, SAVE:: trmb3(klon, nbsrf) ! Point Omega  
290      ! Grandeurs de sorties      ! Grandeurs de sorties
291      REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)      REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)
292      REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)      REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)
293      REAL s_therm(klon), s_trmb1(klon), s_trmb2(klon)      REAL s_therm(klon)
     REAL s_trmb3(klon)  
294    
295      ! Variables pour la convection de K. Emanuel :      ! Variables pour la convection de K. Emanuel :
296    
# Line 337  contains Line 324  contains
324      INTEGER, save:: ibas_con(klon), itop_con(klon)      INTEGER, save:: ibas_con(klon), itop_con(klon)
325      real ema_pct(klon) ! Emanuel pressure at cloud top, in Pa      real ema_pct(klon) ! Emanuel pressure at cloud top, in Pa
326    
327      REAL, save:: rain_con(klon)      REAL rain_con(klon)
328      real rain_lsc(klon)      real rain_lsc(klon)
329      REAL, save:: snow_con(klon) ! neige (mm / s)      REAL snow_con(klon) ! neige (mm / s)
330      real snow_lsc(klon)      real snow_lsc(klon)
331      REAL d_ts(klon, nbsrf)      REAL d_ts(klon, nbsrf) ! variation of ftsol
332    
333      REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)      REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)
334      REAL d_t_vdf(klon, llm), d_q_vdf(klon, llm)      REAL d_t_vdf(klon, llm), d_q_vdf(klon, llm)
# Line 375  contains Line 362  contains
362    
363      REAL zustrdr(klon), zvstrdr(klon)      REAL zustrdr(klon), zvstrdr(klon)
364      REAL zustrli(klon), zvstrli(klon)      REAL zustrli(klon), zvstrli(klon)
     REAL zustrph(klon), zvstrph(klon)  
365      REAL aam, torsfc      REAL aam, torsfc
366    
367      REAL ve_lay(klon, llm) ! transport meri. de l'energie a chaque niveau vert.      REAL ve_lay(klon, llm) ! transport meri. de l'energie a chaque niveau vert.
# Line 383  contains Line 369  contains
369      REAL ue_lay(klon, llm) ! transport zonal de l'energie a chaque niveau vert.      REAL ue_lay(klon, llm) ! transport zonal de l'energie a chaque niveau vert.
370      REAL uq_lay(klon, llm) ! transport zonal de l'eau a chaque niveau vert.      REAL uq_lay(klon, llm) ! transport zonal de l'eau a chaque niveau vert.
371    
372      real date0      REAL tsol(klon)
     REAL ztsol(klon)  
373    
374      REAL d_t_ec(klon, llm)      REAL d_t_ec(klon, llm)
375      ! tendance due \`a la conversion Ec en énergie thermique      ! tendance due \`a la conversion d'\'energie cin\'etique en
376        ! énergie thermique
     REAL ZRCPD  
377    
378      REAL, save:: t2m(klon, nbsrf), q2m(klon, nbsrf)      REAL, save:: t2m(klon, nbsrf), q2m(klon, nbsrf)
379      ! temperature and humidity at 2 m      ! temperature and humidity at 2 m
380    
381      REAL, save:: u10m(klon, nbsrf), v10m(klon, nbsrf) ! vents a 10 m      REAL, save:: u10m_srf(klon, nbsrf), v10m_srf(klon, nbsrf)
382        ! composantes du vent \`a 10 m
383        
384      REAL zt2m(klon), zq2m(klon) ! température, humidité 2 m moyenne sur 1 maille      REAL zt2m(klon), zq2m(klon) ! température, humidité 2 m moyenne sur 1 maille
385      REAL zu10m(klon), zv10m(klon) ! vents a 10 m moyennes sur 1 maille      REAL u10m(klon), v10m(klon) ! vent \`a 10 m moyenn\' sur les sous-surfaces
386    
387      ! Aerosol effects:      ! Aerosol effects:
388    
     REAL sulfate(klon, llm) ! SO4 aerosol concentration (micro g / m3)  
   
     REAL, save:: sulfate_pi(klon, llm)  
     ! SO4 aerosol concentration, in \mu g / m3, pre-industrial value  
   
     REAL cldtaupi(klon, llm)  
     ! cloud optical thickness for pre-industrial aerosols  
   
     REAL re(klon, llm) ! Cloud droplet effective radius  
     REAL fl(klon, llm) ! denominator of re  
   
     ! Aerosol optical properties  
     REAL, save:: tau_ae(klon, llm, 2), piz_ae(klon, llm, 2)  
     REAL, save:: cg_ae(klon, llm, 2)  
   
389      REAL, save:: topswad(klon), solswad(klon) ! aerosol direct effect      REAL, save:: topswad(klon), solswad(klon) ! aerosol direct effect
     REAL, save:: topswai(klon), solswai(klon) ! aerosol indirect effect  
   
390      LOGICAL:: ok_ade = .false. ! apply aerosol direct effect      LOGICAL:: ok_ade = .false. ! apply aerosol direct effect
     LOGICAL:: ok_aie = .false. ! apply aerosol indirect effect  
391    
392      REAL:: bl95_b0 = 2., bl95_b1 = 0.2      REAL:: bl95_b0 = 2., bl95_b1 = 0.2
393      ! Parameters in equation (D) of Boucher and Lohmann (1995, Tellus      ! Parameters in equation (D) of Boucher and Lohmann (1995, Tellus
# Line 432  contains Line 400  contains
400      integer, save:: ncid_startphy      integer, save:: ncid_startphy
401    
402      namelist /physiq_nml/ fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, &      namelist /physiq_nml/ fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, &
403           ratqsbas, ratqshaut, ok_ade, ok_aie, bl95_b0, bl95_b1, &           ratqsbas, ratqshaut, ok_ade, bl95_b0, bl95_b1, iflag_thermals, &
404           iflag_thermals, nsplit_thermals           nsplit_thermals
405    
406      !----------------------------------------------------------------      !----------------------------------------------------------------
407    
# Line 442  contains Line 410  contains
410    
411      test_firstcal: IF (firstcal) THEN      test_firstcal: IF (firstcal) THEN
412         ! initialiser         ! initialiser
413         u10m = 0.         u10m_srf = 0.
414         v10m = 0.         v10m_srf = 0.
415         t2m = 0.         t2m = 0.
416         q2m = 0.         q2m = 0.
417         ffonte = 0.         ffonte = 0.
        fqcalving = 0.  
        piz_ae = 0.  
        tau_ae = 0.  
        cg_ae = 0.  
        rain_con = 0.  
        snow_con = 0.  
        topswai = 0.  
        topswad = 0.  
        solswai = 0.  
        solswad = 0.  
   
418         d_u_con = 0.         d_u_con = 0.
419         d_v_con = 0.         d_v_con = 0.
420         rnebcon0 = 0.         rnebcon0 = 0.
421         clwcon0 = 0.         clwcon0 = 0.
422         rnebcon = 0.         rnebcon = 0.
423         clwcon = 0.         clwcon = 0.
   
424         pblh =0. ! Hauteur de couche limite         pblh =0. ! Hauteur de couche limite
425         plcl =0. ! Niveau de condensation de la CLA         plcl =0. ! Niveau de condensation de la CLA
426         capCL =0. ! CAPE de couche limite         capCL =0. ! CAPE de couche limite
# Line 472  contains Line 428  contains
428         cteiCL =0. ! cloud top instab. crit. couche limite         cteiCL =0. ! cloud top instab. crit. couche limite
429         pblt =0.         pblt =0.
430         therm =0.         therm =0.
        trmb1 =0. ! deep_cape  
        trmb2 =0. ! inhibition  
        trmb3 =0. ! Point Omega  
431    
432         iflag_thermals = 0         iflag_thermals = 0
433         nsplit_thermals = 1         nsplit_thermals = 1
# Line 488  contains Line 441  contains
441    
442         frugs = 0.         frugs = 0.
443         CALL phyetat0(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, &         CALL phyetat0(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, &
444              fevap, rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, &              rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, agesno, &
445              agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &              zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, &
446              q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, &              ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01, &
447              w01, ncid_startphy)              ncid_startphy)
448    
449         ! ATTENTION : il faudra a terme relire q2 dans l'etat initial         ! ATTENTION : il faudra a terme relire q2 dans l'etat initial
450         q2 = 1e-8         q2 = 1e-8
# Line 512  contains Line 465  contains
465            rugoro = 0.            rugoro = 0.
466         ENDIF         ENDIF
467    
        ecrit_ins = NINT(ecrit_ins / dtphys)  
   
468         ! Initialisation des sorties         ! Initialisation des sorties
469           call ini_histins(ok_newmicro)
        call ini_histins(dtphys)  
        CALL ymds2ju(annee_ref, 1, day_ref, 0., date0)  
        ! Positionner date0 pour initialisation de ORCHIDEE  
        print *, 'physiq date0: ', date0  
470         CALL phyredem0         CALL phyredem0
471           call conf_interface
472      ENDIF test_firstcal      ENDIF test_firstcal
473    
474      ! We will modify variables *_seri and we will not touch variables      ! We will modify variables *_seri and we will not touch variables
# Line 532  contains Line 480  contains
480      ql_seri = qx(:, :, iliq)      ql_seri = qx(:, :, iliq)
481      tr_seri = qx(:, :, 3:nqmx)      tr_seri = qx(:, :, 3:nqmx)
482    
483      ztsol = sum(ftsol * pctsrf, dim = 2)      tsol = sum(ftsol * pctsrf, dim = 2)
484    
485      ! Diagnostic de la tendance dynamique :      ! Diagnostic de la tendance dynamique :
486      IF (ancien_ok) THEN      IF (ancien_ok) THEN
# Line 588  contains Line 536  contains
536      CALL orbite(REAL(julien), longi, dist)      CALL orbite(REAL(julien), longi, dist)
537      CALL zenang(longi, time, dtphys * radpas, mu0, fract)      CALL zenang(longi, time, dtphys * radpas, mu0, fract)
538    
539      ! Calcul de l'abedo moyen par maille      CALL pbl_surface(pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &
540      albsol = sum(falbe * pctsrf, dim = 2)           ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, &
541             falbe, fluxlat, rain_fall, snow_fall, frugs, agesno, rugoro, d_t_vdf, &
     ! R\'epartition sous maille des flux longwave et shortwave  
     ! R\'epartition du longwave par sous-surface lin\'earis\'ee  
   
     forall (nsrf = 1: nbsrf)  
        fsollw(:, nsrf) = sollw + 4. * RSIGMA * ztsol**3 &  
             * (ztsol - ftsol(:, nsrf))  
        fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)  
     END forall  
   
     fder = dlw  
   
     CALL clmain(dtphys, pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &  
          ftsol, cdmmax, cdhmax, ksta, ksta_ter, ok_kzmin, ftsoil, qsol, &  
          paprs, play, fsnow, fqsurf, fevap, falbe, fluxlat, rain_fall, &  
          snow_fall, fsolsw, fsollw, fder, frugs, agesno, rugoro, d_t_vdf, &  
542           d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, flux_u, flux_v, &           d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, flux_u, flux_v, &
543           cdragh, cdragm, q2, dsens, devap, ycoefh, yu1, yv1, t2m, q2m, u10m, &           cdragh, cdragm, q2, dflux_t, dflux_q, coefh, t2m, q2m, u10m_srf, &
544           v10m, pblh, capCL, oliqCL, cteiCL, pblT, therm, trmb1, trmb2, trmb3, &           v10m_srf, pblh, capCL, oliqCL, cteiCL, pblT, therm, plcl, fqcalving, &
545           plcl, fqcalving, ffonte, run_off_lic_0)           ffonte, run_off_lic_0, albsol, sollw, solsw, tsol)
546    
547      ! Incr\'ementation des flux      ! Incr\'ementation des flux
548    
549      sens = - sum(flux_t * pctsrf, dim = 2)      sens = - sum(flux_t * pctsrf, dim = 2)
550      evap = - sum(flux_q * pctsrf, dim = 2)      evap = - sum(flux_q * pctsrf, dim = 2)
551      fder = dlw + dsens + devap      fder = dlw + dflux_t + dflux_q
552    
553      DO k = 1, llm      DO k = 1, llm
554         DO i = 1, klon         DO i = 1, klon
# Line 626  contains Line 559  contains
559         ENDDO         ENDDO
560      ENDDO      ENDDO
561    
     ! Update surface temperature:  
   
562      call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf')      call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf')
563      ftsol = ftsol + d_ts      ftsol = ftsol + d_ts ! update surface temperature
564      ztsol = sum(ftsol * pctsrf, dim = 2)      tsol = sum(ftsol * pctsrf, dim = 2)
565      zxfluxlat = sum(fluxlat * pctsrf, dim = 2)      zxfluxlat = sum(fluxlat * pctsrf, dim = 2)
566      zt2m = sum(t2m * pctsrf, dim = 2)      zt2m = sum(t2m * pctsrf, dim = 2)
567      zq2m = sum(q2m * pctsrf, dim = 2)      zq2m = sum(q2m * pctsrf, dim = 2)
568      zu10m = sum(u10m * pctsrf, dim = 2)      u10m = sum(u10m_srf * pctsrf, dim = 2)
569      zv10m = sum(v10m * pctsrf, dim = 2)      v10m = sum(v10m_srf * pctsrf, dim = 2)
570      zxffonte = sum(ffonte * pctsrf, dim = 2)      zxffonte = sum(ffonte * pctsrf, dim = 2)
     zxfqcalving = sum(fqcalving * pctsrf, dim = 2)  
571      s_pblh = sum(pblh * pctsrf, dim = 2)      s_pblh = sum(pblh * pctsrf, dim = 2)
572      s_lcl = sum(plcl * pctsrf, dim = 2)      s_lcl = sum(plcl * pctsrf, dim = 2)
573      s_capCL = sum(capCL * pctsrf, dim = 2)      s_capCL = sum(capCL * pctsrf, dim = 2)
# Line 645  contains Line 575  contains
575      s_cteiCL = sum(cteiCL * pctsrf, dim = 2)      s_cteiCL = sum(cteiCL * pctsrf, dim = 2)
576      s_pblT = sum(pblT * pctsrf, dim = 2)      s_pblT = sum(pblT * pctsrf, dim = 2)
577      s_therm = sum(therm * pctsrf, dim = 2)      s_therm = sum(therm * pctsrf, dim = 2)
     s_trmb1 = sum(trmb1 * pctsrf, dim = 2)  
     s_trmb2 = sum(trmb2 * pctsrf, dim = 2)  
     s_trmb3 = sum(trmb3 * pctsrf, dim = 2)  
578    
579      ! Si une sous-fraction n'existe pas, elle prend la valeur moyenne :      ! Si une sous-fraction n'existe pas, elle prend la valeur moyenne :
580      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
581         DO i = 1, klon         DO i = 1, klon
582            IF (pctsrf(i, nsrf) < epsfra) then            IF (pctsrf(i, nsrf) < epsfra) then
583               ftsol(i, nsrf) = ztsol(i)               ftsol(i, nsrf) = tsol(i)
584               t2m(i, nsrf) = zt2m(i)               t2m(i, nsrf) = zt2m(i)
585               q2m(i, nsrf) = zq2m(i)               q2m(i, nsrf) = zq2m(i)
586               u10m(i, nsrf) = zu10m(i)               u10m_srf(i, nsrf) = u10m(i)
587               v10m(i, nsrf) = zv10m(i)               v10m_srf(i, nsrf) = v10m(i)
588               ffonte(i, nsrf) = zxffonte(i)               ffonte(i, nsrf) = zxffonte(i)
              fqcalving(i, nsrf) = zxfqcalving(i)  
589               pblh(i, nsrf) = s_pblh(i)               pblh(i, nsrf) = s_pblh(i)
590               plcl(i, nsrf) = s_lcl(i)               plcl(i, nsrf) = s_lcl(i)
591               capCL(i, nsrf) = s_capCL(i)               capCL(i, nsrf) = s_capCL(i)
# Line 667  contains Line 593  contains
593               cteiCL(i, nsrf) = s_cteiCL(i)               cteiCL(i, nsrf) = s_cteiCL(i)
594               pblT(i, nsrf) = s_pblT(i)               pblT(i, nsrf) = s_pblT(i)
595               therm(i, nsrf) = s_therm(i)               therm(i, nsrf) = s_therm(i)
              trmb1(i, nsrf) = s_trmb1(i)  
              trmb2(i, nsrf) = s_trmb2(i)  
              trmb3(i, nsrf) = s_trmb3(i)  
596            end IF            end IF
597         ENDDO         ENDDO
598      ENDDO      ENDDO
599    
600      ! Calculer la dérive du flux infrarouge      dlw = - 4. * RSIGMA * tsol**3
   
     DO i = 1, klon  
        dlw(i) = - 4. * RSIGMA * ztsol(i)**3  
     ENDDO  
601    
602      ! Appeler la convection      ! Appeler la convection
603    
604      if (conv_emanuel) then      if (conv_emanuel) then
605         CALL concvl(paprs, play, t_seri, q_seri, u_seri, v_seri, sig1, w01, &         CALL concvl(paprs, play, t_seri, q_seri, u_seri, v_seri, sig1, w01, &
606              d_t_con, d_q_con, d_u_con, d_v_con, rain_con, ibas_con, itop_con, &              d_t_con, d_q_con, d_u_con, d_v_con, rain_con, ibas_con, itop_con, &
607              upwd, dnwd, Ma, cape, iflagctrl, qcondc, pmflxr, da, phi, mp)              upwd, dnwd, Ma, cape, iflagctrl, clwcon0, pmflxr, da, phi, mp)
608         snow_con = 0.         snow_con = 0.
        clwcon0 = qcondc  
609         mfu = upwd + dnwd         mfu = upwd + dnwd
610    
611         zqsat = MIN(0.5, r2es * FOEEW(t_seri, rtt >= t_seri) / play)         zqsat = MIN(0.5, r2es * FOEEW(t_seri, rtt >= t_seri) / play)
# Line 708  contains Line 626  contains
626         conv_q = d_q_dyn + d_q_vdf / dtphys         conv_q = d_q_dyn + d_q_vdf / dtphys
627         conv_t = d_t_dyn + d_t_vdf / dtphys         conv_t = d_t_dyn + d_t_vdf / dtphys
628         z_avant = sum((q_seri + ql_seri) * zmasse, dim=2)         z_avant = sum((q_seri + ql_seri) * zmasse, dim=2)
629         CALL conflx(dtphys, paprs, play, t_seri(:, llm:1:- 1), &         CALL conflx(paprs, play, t_seri(:, llm:1:- 1), q_seri(:, llm:1:- 1), &
630              q_seri(:, llm:1:- 1), conv_t, conv_q, - evap, omega, &              conv_t, conv_q, - evap, omega, d_t_con, d_q_con, rain_con, &
631              d_t_con, d_q_con, rain_con, snow_con, mfu(:, llm:1:- 1), &              snow_con, mfu(:, llm:1:- 1), mfd(:, llm:1:- 1), pen_u, pde_u, &
632              mfd(:, llm:1:- 1), pen_u, pde_u, pen_d, pde_d, kcbot, kctop, &              pen_d, pde_d, kcbot, kctop, kdtop, pmflxr, pmflxs)
             kdtop, pmflxr, pmflxs)  
633         WHERE (rain_con < 0.) rain_con = 0.         WHERE (rain_con < 0.) rain_con = 0.
634         WHERE (snow_con < 0.) snow_con = 0.         WHERE (snow_con < 0.) snow_con = 0.
635         ibas_con = llm + 1 - kcbot         ibas_con = llm + 1 - kcbot
# Line 755  contains Line 672  contains
672         t_seri = t_seri + d_t_ajs         t_seri = t_seri + d_t_ajs
673         q_seri = q_seri + d_q_ajs         q_seri = q_seri + d_q_ajs
674      else      else
675         call calltherm(dtphys, play, paprs, pphi, u_seri, v_seri, t_seri, &         call calltherm(play, paprs, pphi, u_seri, v_seri, t_seri, q_seri, &
676              q_seri, d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm)              d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm)
677      endif      endif
678    
679      ! Caclul des ratqs      ! Caclul des ratqs
680    
     ! ratqs convectifs \`a l'ancienne en fonction de (q(z = 0) - q) / q  
     ! on \'ecrase le tableau ratqsc calcul\'e par clouds_gno  
681      if (iflag_cldcon == 1) then      if (iflag_cldcon == 1) then
682           ! ratqs convectifs \`a l'ancienne en fonction de (q(z = 0) - q) / q
683           ! on \'ecrase le tableau ratqsc calcul\'e par clouds_gno
684         do k = 1, llm         do k = 1, llm
685            do i = 1, klon            do i = 1, klon
686               if(ptconv(i, k)) then               if(ptconv(i, k)) then
# Line 797  contains Line 714  contains
714         ratqs = ratqss         ratqs = ratqss
715      endif      endif
716    
717      CALL fisrtilp(dtphys, paprs, play, t_seri, q_seri, ptconv, ratqs, &      CALL fisrtilp(paprs, play, t_seri, q_seri, ptconv, ratqs, d_t_lsc, &
718           d_t_lsc, d_q_lsc, d_ql_lsc, rneb, cldliq, rain_lsc, snow_lsc, &           d_q_lsc, d_ql_lsc, rneb, cldliq, rain_lsc, snow_lsc, pfrac_impa, &
719           pfrac_impa, pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, &           pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, psfl, rhcl)
          psfl, rhcl)  
720    
721      WHERE (rain_lsc < 0) rain_lsc = 0.      WHERE (rain_lsc < 0) rain_lsc = 0.
722      WHERE (snow_lsc < 0) snow_lsc = 0.      WHERE (snow_lsc < 0) snow_lsc = 0.
# Line 900  contains Line 816  contains
816         ENDDO         ENDDO
817      ENDDO      ENDDO
818    
     ! Introduce the aerosol direct and first indirect radiative forcings:  
     tau_ae = 0.  
     piz_ae = 0.  
     cg_ae = 0.  
   
819      ! Param\`etres optiques des nuages et quelques param\`etres pour      ! Param\`etres optiques des nuages et quelques param\`etres pour
820      ! diagnostics :      ! diagnostics :
821      if (ok_newmicro) then      if (ok_newmicro) then
822         CALL newmicro(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, &         CALL newmicro(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, &
823              cldh, cldl, cldm, cldt, cldq, flwp, fiwp, flwc, fiwc, ok_aie, &              cldh, cldl, cldm, cldt, cldq, flwp, fiwp, flwc, fiwc)
             sulfate, sulfate_pi, bl95_b0, bl95_b1, cldtaupi, re, fl)  
824      else      else
825         CALL nuage(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, cldh, &         CALL nuage(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, cldh, &
826              cldl, cldm, cldt, cldq, ok_aie, sulfate, sulfate_pi, bl95_b0, &              cldl, cldm, cldt, cldq)
             bl95_b1, cldtaupi, re, fl)  
827      endif      endif
828    
829      IF (MOD(itap - 1, radpas) == 0) THEN      IF (MOD(itap - 1, radpas) == 0) THEN
        ! Prescrire l'ozone :  
830         wo = ozonecm(REAL(julien), paprs)         wo = ozonecm(REAL(julien), paprs)
   
        ! Appeler le rayonnement mais calculer tout d'abord l'albedo du sol.  
        ! Calcul de l'abedo moyen par maille  
831         albsol = sum(falbe * pctsrf, dim = 2)         albsol = sum(falbe * pctsrf, dim = 2)
832           CALL radlwsw(dist, mu0, fract, paprs, play, tsol, albsol, t_seri, &
        ! Rayonnement (compatible Arpege-IFS) :  
        CALL radlwsw(dist, mu0, fract, paprs, play, ztsol, albsol, t_seri, &  
833              q_seri, wo, cldfra, cldemi, cldtau, heat, heat0, cool, cool0, &              q_seri, wo, cldfra, cldemi, cldtau, heat, heat0, cool, cool0, &
834              radsol, albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, &              radsol, albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, &
835              toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, &              toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, &
836              swup0, swup, ok_ade, ok_aie, tau_ae, piz_ae, cg_ae, topswad, &              swup0, swup, ok_ade, topswad, solswad)
             solswad, cldtaupi, topswai, solswai)  
837      ENDIF      ENDIF
838    
839      ! Ajouter la tendance des rayonnements (tous les pas)      ! Ajouter la tendance des rayonnements (tous les pas)
# Line 942  contains Line 844  contains
844         ENDDO         ENDDO
845      ENDDO      ENDDO
846    
     ! Calculer l'hydrologie de la surface  
     zxqsurf = sum(fqsurf * pctsrf, dim = 2)  
     zxsnow = sum(fsnow * pctsrf, dim = 2)  
   
847      ! Calculer le bilan du sol et la d\'erive de temp\'erature (couplage)      ! Calculer le bilan du sol et la d\'erive de temp\'erature (couplage)
848      DO i = 1, klon      DO i = 1, klon
849         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)
# Line 955  contains Line 853  contains
853    
854      IF (ok_orodr) THEN      IF (ok_orodr) THEN
855         ! S\'election des points pour lesquels le sch\'ema est actif :         ! S\'election des points pour lesquels le sch\'ema est actif :
        igwd = 0  
856         DO i = 1, klon         DO i = 1, klon
857            itest(i) = 0            ktest(i) = 0
858            IF (zpic(i) - zmea(i) > 100. .AND. zstd(i) > 10.) THEN            IF (zpic(i) - zmea(i) > 100. .AND. zstd(i) > 10.) THEN
859               itest(i) = 1               ktest(i) = 1
              igwd = igwd + 1  
860            ENDIF            ENDIF
861         ENDDO         ENDDO
862    
863         CALL drag_noro(klon, llm, dtphys, paprs, play, zmea, zstd, zsig, zgam, &         CALL drag_noro(paprs, play, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
864              zthe, zpic, zval, itest, t_seri, u_seri, v_seri, zulow, zvlow, &              ktest, t_seri, u_seri, v_seri, zulow, zvlow, zustrdr, zvstrdr, &
865              zustrdr, zvstrdr, d_t_oro, d_u_oro, d_v_oro)              d_t_oro, d_u_oro, d_v_oro)
866    
867         ! ajout des tendances         ! ajout des tendances
868         DO k = 1, llm         DO k = 1, llm
# Line 980  contains Line 876  contains
876    
877      IF (ok_orolf) THEN      IF (ok_orolf) THEN
878         ! S\'election des points pour lesquels le sch\'ema est actif :         ! S\'election des points pour lesquels le sch\'ema est actif :
        igwd = 0  
879         DO i = 1, klon         DO i = 1, klon
880            itest(i) = 0            ktest(i) = 0
881            IF (zpic(i) - zmea(i) > 100.) THEN            IF (zpic(i) - zmea(i) > 100.) THEN
882               itest(i) = 1               ktest(i) = 1
              igwd = igwd + 1  
883            ENDIF            ENDIF
884         ENDDO         ENDDO
885    
886         CALL lift_noro(klon, llm, dtphys, paprs, play, rlat, zmea, zstd, zpic, &         CALL lift_noro(paprs, play, zmea, zstd, zpic, ktest, t_seri, u_seri, &
887              itest, t_seri, u_seri, v_seri, zulow, zvlow, zustrli, zvstrli, &              v_seri, zulow, zvlow, zustrli, zvstrli, d_t_lif, d_u_lif, d_v_lif)
             d_t_lif, d_u_lif, d_v_lif)  
888    
889         ! Ajout des tendances :         ! Ajout des tendances :
890         DO k = 1, llm         DO k = 1, llm
# Line 1003  contains Line 896  contains
896         ENDDO         ENDDO
897      ENDIF      ENDIF
898    
899      ! Stress n\'ecessaires : toute la physique      CALL aaam_bud(rg, romega, pphis, zustrdr, zustrli, &
900             sum((u_seri - u) / dtphys * zmasse, dim = 2), zvstrdr, &
901      DO i = 1, klon           zvstrli, sum((v_seri - v) / dtphys * zmasse, dim = 2), paprs, u, v, &
902         zustrph(i) = 0.           aam, torsfc)
        zvstrph(i) = 0.  
     ENDDO  
     DO k = 1, llm  
        DO i = 1, klon  
           zustrph(i) = zustrph(i) + (u_seri(i, k) - u(i, k)) / dtphys &  
                * zmasse(i, k)  
           zvstrph(i) = zvstrph(i) + (v_seri(i, k) - v(i, k)) / dtphys &  
                * zmasse(i, k)  
        ENDDO  
     ENDDO  
   
     CALL aaam_bud(rg, romega, rlat, rlon, pphis, zustrdr, zustrli, zustrph, &  
          zvstrdr, zvstrli, zvstrph, paprs, u, v, aam, torsfc)  
903    
904      ! Calcul des tendances traceurs      ! Calcul des tendances traceurs
905      call phytrac(julien, time, firstcal, lafin, dtphys, t, paprs, play, mfu, &      call phytrac(julien, time, firstcal, lafin, t, paprs, play, mfu, mfd, &
906           mfd, pde_u, pen_d, ycoefh, fm_therm, entr_therm, yu1, yv1, ftsol, &           pde_u, pen_d, coefh, cdragh, fm_therm, entr_therm, u(:, 1), v(:, 1), &
907           pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, tr_seri, &           ftsol, pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, &
908           zmasse, ncid_startphy)           tr_seri, zmasse, ncid_startphy)
   
     IF (offline) call phystokenc(dtphys, t, mfu, mfd, pen_u, pde_u, pen_d, &  
          pde_d, fm_therm, entr_therm, ycoefh, yu1, yv1, ftsol, pctsrf, &  
          frac_impa, frac_nucl, pphis, airephy, dtphys)  
909    
910      ! Calculer le transport de l'eau et de l'energie (diagnostique)      ! Calculer le transport de l'eau et de l'energie (diagnostique)
911      CALL transp(paprs, t_seri, q_seri, u_seri, v_seri, zphi, ve, vq, ue, uq)      CALL transp(paprs, t_seri, q_seri, u_seri, v_seri, zphi, ve, vq, ue, uq)
# Line 1044  contains Line 920  contains
920      ! conversion Ec en énergie thermique      ! conversion Ec en énergie thermique
921      DO k = 1, llm      DO k = 1, llm
922         DO i = 1, klon         DO i = 1, klon
923            ZRCPD = RCPD * (1. + RVTMP2 * q_seri(i, k))            d_t_ec(i, k) = 0.5 / (RCPD * (1. + RVTMP2 * q_seri(i, k))) &
           d_t_ec(i, k) = 0.5 / ZRCPD &  
924                 * (u(i, k)**2 + v(i, k)**2 - u_seri(i, k)**2 - v_seri(i, k)**2)                 * (u(i, k)**2 + v(i, k)**2 - u_seri(i, k)**2 - v_seri(i, k)**2)
925            t_seri(i, k) = t_seri(i, k) + d_t_ec(i, k)            t_seri(i, k) = t_seri(i, k) + d_t_ec(i, k)
926            d_t_ec(i, k) = d_t_ec(i, k) / dtphys            d_t_ec(i, k) = d_t_ec(i, k) / dtphys
# Line 1096  contains Line 971  contains
971      CALL histwrite_phy("precip", rain_fall + snow_fall)      CALL histwrite_phy("precip", rain_fall + snow_fall)
972      CALL histwrite_phy("plul", rain_lsc + snow_lsc)      CALL histwrite_phy("plul", rain_lsc + snow_lsc)
973      CALL histwrite_phy("pluc", rain_con + snow_con)      CALL histwrite_phy("pluc", rain_con + snow_con)
974      CALL histwrite_phy("tsol", ztsol)      CALL histwrite_phy("tsol", tsol)
975      CALL histwrite_phy("t2m", zt2m)      CALL histwrite_phy("t2m", zt2m)
976      CALL histwrite_phy("q2m", zq2m)      CALL histwrite_phy("q2m", zq2m)
977      CALL histwrite_phy("u10m", zu10m)      CALL histwrite_phy("u10m", u10m)
978      CALL histwrite_phy("v10m", zv10m)      CALL histwrite_phy("v10m", v10m)
979      CALL histwrite_phy("snow", snow_fall)      CALL histwrite_phy("snow", snow_fall)
980      CALL histwrite_phy("cdrm", cdragm)      CALL histwrite_phy("cdrm", cdragm)
981      CALL histwrite_phy("cdrh", cdragh)      CALL histwrite_phy("cdrh", cdragh)
# Line 1116  contains Line 991  contains
991      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))
992      CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))      CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))
993      CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))      CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))
994        CALL histwrite_phy("zxfqcalving", sum(fqcalving * pctsrf, dim = 2))
     DO nsrf = 1, nbsrf  
        CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)  
        CALL histwrite_phy("fract_"//clnsurf(nsrf), pctsrf(:, nsrf))  
        CALL histwrite_phy("sens_"//clnsurf(nsrf), flux_t(:, nsrf))  
        CALL histwrite_phy("lat_"//clnsurf(nsrf), fluxlat(:, nsrf))  
        CALL histwrite_phy("tsol_"//clnsurf(nsrf), ftsol(:, nsrf))  
        CALL histwrite_phy("taux_"//clnsurf(nsrf), flux_u(:, nsrf))  
        CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))  
        CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))  
        CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))  
     END DO  
   
995      CALL histwrite_phy("albs", albsol)      CALL histwrite_phy("albs", albsol)
996      CALL histwrite_phy("tro3", wo * dobson_u * 1e3 / zmasse / rmo3 * md)      CALL histwrite_phy("tro3", wo * dobson_u * 1e3 / zmasse / rmo3 * md)
997      CALL histwrite_phy("rugs", zxrugs)      CALL histwrite_phy("rugs", zxrugs)
# Line 1139  contains Line 1002  contains
1002      CALL histwrite_phy("s_oliqCL", s_oliqCL)      CALL histwrite_phy("s_oliqCL", s_oliqCL)
1003      CALL histwrite_phy("s_cteiCL", s_cteiCL)      CALL histwrite_phy("s_cteiCL", s_cteiCL)
1004      CALL histwrite_phy("s_therm", s_therm)      CALL histwrite_phy("s_therm", s_therm)
     CALL histwrite_phy("s_trmb1", s_trmb1)  
     CALL histwrite_phy("s_trmb2", s_trmb2)  
     CALL histwrite_phy("s_trmb3", s_trmb3)  
   
     if (conv_emanuel) then  
        CALL histwrite_phy("ptop", ema_pct)  
        CALL histwrite_phy("dnwd0", - mp)  
     end if  
   
1005      CALL histwrite_phy("temp", t_seri)      CALL histwrite_phy("temp", t_seri)
1006      CALL histwrite_phy("vitu", u_seri)      CALL histwrite_phy("vitu", u_seri)
1007      CALL histwrite_phy("vitv", v_seri)      CALL histwrite_phy("vitv", v_seri)
# Line 1156  contains Line 1010  contains
1010      CALL histwrite_phy("dtvdf", d_t_vdf)      CALL histwrite_phy("dtvdf", d_t_vdf)
1011      CALL histwrite_phy("dqvdf", d_q_vdf)      CALL histwrite_phy("dqvdf", d_q_vdf)
1012      CALL histwrite_phy("rhum", zx_rh)      CALL histwrite_phy("rhum", zx_rh)
1013        CALL histwrite_phy("d_t_ec", d_t_ec)
1014        CALL histwrite_phy("dtsw0", heat0 / 86400.)
1015        CALL histwrite_phy("dtlw0", - cool0 / 86400.)
1016        CALL histwrite_phy("msnow", sum(fsnow * pctsrf, dim = 2))
1017        call histwrite_phy("qsurf", sum(fqsurf * pctsrf, dim = 2))
1018        call histwrite_phy("flat", zxfluxlat)
1019    
1020        DO nsrf = 1, nbsrf
1021           CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)
1022           CALL histwrite_phy("fract_"//clnsurf(nsrf), pctsrf(:, nsrf))
1023           CALL histwrite_phy("sens_"//clnsurf(nsrf), flux_t(:, nsrf))
1024           CALL histwrite_phy("lat_"//clnsurf(nsrf), fluxlat(:, nsrf))
1025           CALL histwrite_phy("tsol_"//clnsurf(nsrf), ftsol(:, nsrf))
1026           CALL histwrite_phy("taux_"//clnsurf(nsrf), flux_u(:, nsrf))
1027           CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))
1028           CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))
1029           CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))
1030           CALL histwrite_phy("u10m_"//clnsurf(nsrf), u10m_srf(:, nsrf))
1031           CALL histwrite_phy("v10m_"//clnsurf(nsrf), v10m_srf(:, nsrf))
1032        END DO
1033    
1034        if (conv_emanuel) then
1035           CALL histwrite_phy("ptop", ema_pct)
1036           CALL histwrite_phy("dnwd0", - mp)
1037        end if
1038    
1039      if (ok_instan) call histsync(nid_ins)      if (ok_instan) call histsync(nid_ins)
1040    
1041      IF (lafin) then      IF (lafin) then
1042         call NF95_CLOSE(ncid_startphy)         call NF95_CLOSE(ncid_startphy)
1043         CALL phyredem(pctsrf, ftsol, ftsoil, fqsurf, qsol, &         CALL phyredem(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, &
1044              fsnow, falbe, fevap, rain_fall, snow_fall, solsw, sollw, dlw, &              rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, agesno, &
1045              radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &              zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, &
1046              t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, &              rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
             w01)  
1047      end IF      end IF
1048    
1049      firstcal = .FALSE.      firstcal = .FALSE.

Legend:
Removed from v.212  
changed lines
  Added in v.307

  ViewVC Help
Powered by ViewVC 1.1.21