/[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 214 by guez, Wed Mar 22 13:40:27 2017 UTC trunk/phylmd/physiq.f revision 305 by guez, Tue Sep 11 11:08:38 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    
     REAL, save:: fevap(klon, nbsrf) ! evaporation  
153      REAL fluxlat(klon, nbsrf)      REAL 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 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 276  contains Line 270  contains
270      REAL cldl(klon), cldm(klon), cldh(klon) ! nuages bas, moyen et haut      REAL cldl(klon), cldm(klon), cldh(klon) ! nuages bas, moyen et haut
271      REAL cldt(klon), cldq(klon) ! nuage total, eau liquide integree      REAL cldt(klon), cldq(klon) ! nuage total, eau liquide integree
272    
273      REAL zxqsurf(klon), zxsnow(klon), zxfluxlat(klon)      REAL zxfluxlat(klon)
   
274      REAL dist, mu0(klon), fract(klon)      REAL dist, mu0(klon), fract(klon)
275      real longi      real longi
276      REAL z_avant(klon), z_apres(klon), z_factor(klon)      REAL z_avant(klon), z_apres(klon), z_factor(klon)
# Line 296  contains Line 289  contains
289      REAL, SAVE:: cteiCL(klon, nbsrf) ! cloud top instab. crit. couche limite      REAL, SAVE:: cteiCL(klon, nbsrf) ! cloud top instab. crit. couche limite
290      REAL, SAVE:: pblt(klon, nbsrf) ! T \`a la hauteur de couche limite      REAL, SAVE:: pblt(klon, nbsrf) ! T \`a la hauteur de couche limite
291      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  
292      ! Grandeurs de sorties      ! Grandeurs de sorties
293      REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)      REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)
294      REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)      REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)
295      REAL s_therm(klon), s_trmb1(klon), s_trmb2(klon)      REAL s_therm(klon)
     REAL s_trmb3(klon)  
296    
297      ! Variables pour la convection de K. Emanuel :      ! Variables pour la convection de K. Emanuel :
298    
# Line 337  contains Line 326  contains
326      INTEGER, save:: ibas_con(klon), itop_con(klon)      INTEGER, save:: ibas_con(klon), itop_con(klon)
327      real ema_pct(klon) ! Emanuel pressure at cloud top, in Pa      real ema_pct(klon) ! Emanuel pressure at cloud top, in Pa
328    
329      REAL, save:: rain_con(klon)      REAL rain_con(klon)
330      real rain_lsc(klon)      real rain_lsc(klon)
331      REAL, save:: snow_con(klon) ! neige (mm / s)      REAL snow_con(klon) ! neige (mm / s)
332      real snow_lsc(klon)      real snow_lsc(klon)
333      REAL d_ts(klon, nbsrf)      REAL d_ts(klon, nbsrf) ! variation of ftsol
334    
335      REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)      REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)
336      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 364  contains
364    
365      REAL zustrdr(klon), zvstrdr(klon)      REAL zustrdr(klon), zvstrdr(klon)
366      REAL zustrli(klon), zvstrli(klon)      REAL zustrli(klon), zvstrli(klon)
     REAL zustrph(klon), zvstrph(klon)  
367      REAL aam, torsfc      REAL aam, torsfc
368    
369      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 371  contains
371      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.
372      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.
373    
374      real date0      REAL tsol(klon)
     REAL ztsol(klon)  
375    
376      REAL d_t_ec(klon, llm)      REAL d_t_ec(klon, llm)
377      ! tendance due \`a la conversion d'\'energie cin\'etique en      ! tendance due \`a la conversion d'\'energie cin\'etique en
# Line 393  contains Line 380  contains
380      REAL, save:: t2m(klon, nbsrf), q2m(klon, nbsrf)      REAL, save:: t2m(klon, nbsrf), q2m(klon, nbsrf)
381      ! temperature and humidity at 2 m      ! temperature and humidity at 2 m
382    
383      REAL, save:: u10m(klon, nbsrf), v10m(klon, nbsrf) ! vents a 10 m      REAL, save:: u10m_srf(klon, nbsrf), v10m_srf(klon, nbsrf)
384        ! composantes du vent \`a 10 m
385        
386      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
387      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
388    
389      ! Aerosol effects:      ! Aerosol effects:
390    
     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)  
   
391      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  
   
392      LOGICAL:: ok_ade = .false. ! apply aerosol direct effect      LOGICAL:: ok_ade = .false. ! apply aerosol direct effect
     LOGICAL:: ok_aie = .false. ! apply aerosol indirect effect  
393    
394      REAL:: bl95_b0 = 2., bl95_b1 = 0.2      REAL:: bl95_b0 = 2., bl95_b1 = 0.2
395      ! Parameters in equation (D) of Boucher and Lohmann (1995, Tellus      ! Parameters in equation (D) of Boucher and Lohmann (1995, Tellus
# Line 431  contains Line 402  contains
402      integer, save:: ncid_startphy      integer, save:: ncid_startphy
403    
404      namelist /physiq_nml/ fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, &      namelist /physiq_nml/ fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, &
405           ratqsbas, ratqshaut, ok_ade, ok_aie, bl95_b0, bl95_b1, &           ratqsbas, ratqshaut, ok_ade, bl95_b0, bl95_b1, iflag_thermals, &
406           iflag_thermals, nsplit_thermals           nsplit_thermals
407    
408      !----------------------------------------------------------------      !----------------------------------------------------------------
409    
# Line 441  contains Line 412  contains
412    
413      test_firstcal: IF (firstcal) THEN      test_firstcal: IF (firstcal) THEN
414         ! initialiser         ! initialiser
415         u10m = 0.         u10m_srf = 0.
416         v10m = 0.         v10m_srf = 0.
417         t2m = 0.         t2m = 0.
418         q2m = 0.         q2m = 0.
419         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.  
   
420         d_u_con = 0.         d_u_con = 0.
421         d_v_con = 0.         d_v_con = 0.
422         rnebcon0 = 0.         rnebcon0 = 0.
423         clwcon0 = 0.         clwcon0 = 0.
424         rnebcon = 0.         rnebcon = 0.
425         clwcon = 0.         clwcon = 0.
   
426         pblh =0. ! Hauteur de couche limite         pblh =0. ! Hauteur de couche limite
427         plcl =0. ! Niveau de condensation de la CLA         plcl =0. ! Niveau de condensation de la CLA
428         capCL =0. ! CAPE de couche limite         capCL =0. ! CAPE de couche limite
# Line 471  contains Line 430  contains
430         cteiCL =0. ! cloud top instab. crit. couche limite         cteiCL =0. ! cloud top instab. crit. couche limite
431         pblt =0.         pblt =0.
432         therm =0.         therm =0.
        trmb1 =0. ! deep_cape  
        trmb2 =0. ! inhibition  
        trmb3 =0. ! Point Omega  
433    
434         iflag_thermals = 0         iflag_thermals = 0
435         nsplit_thermals = 1         nsplit_thermals = 1
# Line 487  contains Line 443  contains
443    
444         frugs = 0.         frugs = 0.
445         CALL phyetat0(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, &         CALL phyetat0(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, &
446              fevap, rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, &              rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, agesno, &
447              agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &              zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, &
448              q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, &              ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01, &
449              w01, ncid_startphy)              ncid_startphy)
450    
451         ! ATTENTION : il faudra a terme relire q2 dans l'etat initial         ! ATTENTION : il faudra a terme relire q2 dans l'etat initial
452         q2 = 1e-8         q2 = 1e-8
# Line 511  contains Line 467  contains
467            rugoro = 0.            rugoro = 0.
468         ENDIF         ENDIF
469    
        ecrit_ins = NINT(ecrit_ins / dtphys)  
   
470         ! Initialisation des sorties         ! Initialisation des sorties
471           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  
472         CALL phyredem0         CALL phyredem0
473           call conf_interface
474      ENDIF test_firstcal      ENDIF test_firstcal
475    
476      ! We will modify variables *_seri and we will not touch variables      ! We will modify variables *_seri and we will not touch variables
# Line 531  contains Line 482  contains
482      ql_seri = qx(:, :, iliq)      ql_seri = qx(:, :, iliq)
483      tr_seri = qx(:, :, 3:nqmx)      tr_seri = qx(:, :, 3:nqmx)
484    
485      ztsol = sum(ftsol * pctsrf, dim = 2)      tsol = sum(ftsol * pctsrf, dim = 2)
486    
487      ! Diagnostic de la tendance dynamique :      ! Diagnostic de la tendance dynamique :
488      IF (ancien_ok) THEN      IF (ancien_ok) THEN
# Line 586  contains Line 537  contains
537    
538      CALL orbite(REAL(julien), longi, dist)      CALL orbite(REAL(julien), longi, dist)
539      CALL zenang(longi, time, dtphys * radpas, mu0, fract)      CALL zenang(longi, time, dtphys * radpas, mu0, fract)
   
     ! Calcul de l'abedo moyen par maille  
540      albsol = sum(falbe * pctsrf, dim = 2)      albsol = sum(falbe * pctsrf, dim = 2)
541    
542      ! R\'epartition sous maille des flux longwave et shortwave      ! R\'epartition sous maille des flux longwave et shortwave
543      ! R\'epartition du longwave par sous-surface lin\'earis\'ee      ! R\'epartition du longwave par sous-surface lin\'earis\'ee
544    
545      forall (nsrf = 1: nbsrf)      forall (nsrf = 1: nbsrf)
546         fsollw(:, nsrf) = sollw + 4. * RSIGMA * ztsol**3 &         fsollw(:, nsrf) = sollw + 4. * RSIGMA * tsol**3 &
547              * (ztsol - ftsol(:, nsrf))              * (tsol - ftsol(:, nsrf))
548         fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)         fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)
549      END forall      END forall
550    
551      fder = dlw      CALL pbl_surface(pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &
552             ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, &
553      CALL clmain(dtphys, pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &           falbe, fluxlat, rain_fall, snow_fall, fsolsw, fsollw, frugs, agesno, &
554           ftsol, cdmmax, cdhmax, ksta, ksta_ter, ok_kzmin, ftsoil, qsol, &           rugoro, d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, &
555           paprs, play, fsnow, fqsurf, fevap, falbe, fluxlat, rain_fall, &           flux_u, flux_v, cdragh, cdragm, q2, dflux_t, dflux_q, coefh, t2m, &
556           snow_fall, fsolsw, fsollw, fder, frugs, agesno, rugoro, d_t_vdf, &           q2m, u10m_srf, v10m_srf, pblh, capCL, oliqCL, cteiCL, pblT, therm, &
          d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, flux_u, flux_v, &  
          cdragh, cdragm, q2, dsens, devap, ycoefh, yu1, yv1, t2m, q2m, u10m, &  
          v10m, pblh, capCL, oliqCL, cteiCL, pblT, therm, trmb1, trmb2, trmb3, &  
557           plcl, fqcalving, ffonte, run_off_lic_0)           plcl, fqcalving, ffonte, run_off_lic_0)
558    
559      ! Incr\'ementation des flux      ! Incr\'ementation des flux
560    
561      sens = - sum(flux_t * pctsrf, dim = 2)      sens = - sum(flux_t * pctsrf, dim = 2)
562      evap = - sum(flux_q * pctsrf, dim = 2)      evap = - sum(flux_q * pctsrf, dim = 2)
563      fder = dlw + dsens + devap      fder = dlw + dflux_t + dflux_q
564    
565      DO k = 1, llm      DO k = 1, llm
566         DO i = 1, klon         DO i = 1, klon
# Line 625  contains Line 571  contains
571         ENDDO         ENDDO
572      ENDDO      ENDDO
573    
     ! Update surface temperature:  
   
574      call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf')      call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf')
575      ftsol = ftsol + d_ts      ftsol = ftsol + d_ts ! update surface temperature
576      ztsol = sum(ftsol * pctsrf, dim = 2)      tsol = sum(ftsol * pctsrf, dim = 2)
577      zxfluxlat = sum(fluxlat * pctsrf, dim = 2)      zxfluxlat = sum(fluxlat * pctsrf, dim = 2)
578      zt2m = sum(t2m * pctsrf, dim = 2)      zt2m = sum(t2m * pctsrf, dim = 2)
579      zq2m = sum(q2m * pctsrf, dim = 2)      zq2m = sum(q2m * pctsrf, dim = 2)
580      zu10m = sum(u10m * pctsrf, dim = 2)      u10m = sum(u10m_srf * pctsrf, dim = 2)
581      zv10m = sum(v10m * pctsrf, dim = 2)      v10m = sum(v10m_srf * pctsrf, dim = 2)
582      zxffonte = sum(ffonte * pctsrf, dim = 2)      zxffonte = sum(ffonte * pctsrf, dim = 2)
     zxfqcalving = sum(fqcalving * pctsrf, dim = 2)  
583      s_pblh = sum(pblh * pctsrf, dim = 2)      s_pblh = sum(pblh * pctsrf, dim = 2)
584      s_lcl = sum(plcl * pctsrf, dim = 2)      s_lcl = sum(plcl * pctsrf, dim = 2)
585      s_capCL = sum(capCL * pctsrf, dim = 2)      s_capCL = sum(capCL * pctsrf, dim = 2)
# Line 644  contains Line 587  contains
587      s_cteiCL = sum(cteiCL * pctsrf, dim = 2)      s_cteiCL = sum(cteiCL * pctsrf, dim = 2)
588      s_pblT = sum(pblT * pctsrf, dim = 2)      s_pblT = sum(pblT * pctsrf, dim = 2)
589      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)  
590    
591      ! Si une sous-fraction n'existe pas, elle prend la valeur moyenne :      ! Si une sous-fraction n'existe pas, elle prend la valeur moyenne :
592      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
593         DO i = 1, klon         DO i = 1, klon
594            IF (pctsrf(i, nsrf) < epsfra) then            IF (pctsrf(i, nsrf) < epsfra) then
595               ftsol(i, nsrf) = ztsol(i)               ftsol(i, nsrf) = tsol(i)
596               t2m(i, nsrf) = zt2m(i)               t2m(i, nsrf) = zt2m(i)
597               q2m(i, nsrf) = zq2m(i)               q2m(i, nsrf) = zq2m(i)
598               u10m(i, nsrf) = zu10m(i)               u10m_srf(i, nsrf) = u10m(i)
599               v10m(i, nsrf) = zv10m(i)               v10m_srf(i, nsrf) = v10m(i)
600               ffonte(i, nsrf) = zxffonte(i)               ffonte(i, nsrf) = zxffonte(i)
              fqcalving(i, nsrf) = zxfqcalving(i)  
601               pblh(i, nsrf) = s_pblh(i)               pblh(i, nsrf) = s_pblh(i)
602               plcl(i, nsrf) = s_lcl(i)               plcl(i, nsrf) = s_lcl(i)
603               capCL(i, nsrf) = s_capCL(i)               capCL(i, nsrf) = s_capCL(i)
# Line 666  contains Line 605  contains
605               cteiCL(i, nsrf) = s_cteiCL(i)               cteiCL(i, nsrf) = s_cteiCL(i)
606               pblT(i, nsrf) = s_pblT(i)               pblT(i, nsrf) = s_pblT(i)
607               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)  
608            end IF            end IF
609         ENDDO         ENDDO
610      ENDDO      ENDDO
611    
612      ! Calculer la dérive du flux infrarouge      dlw = - 4. * RSIGMA * tsol**3
   
     DO i = 1, klon  
        dlw(i) = - 4. * RSIGMA * ztsol(i)**3  
     ENDDO  
613    
614      ! Appeler la convection      ! Appeler la convection
615    
616      if (conv_emanuel) then      if (conv_emanuel) then
617         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, &
618              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, &
619              upwd, dnwd, Ma, cape, iflagctrl, qcondc, pmflxr, da, phi, mp)              upwd, dnwd, Ma, cape, iflagctrl, clwcon0, pmflxr, da, phi, mp)
620         snow_con = 0.         snow_con = 0.
        clwcon0 = qcondc  
621         mfu = upwd + dnwd         mfu = upwd + dnwd
622    
623         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 707  contains Line 638  contains
638         conv_q = d_q_dyn + d_q_vdf / dtphys         conv_q = d_q_dyn + d_q_vdf / dtphys
639         conv_t = d_t_dyn + d_t_vdf / dtphys         conv_t = d_t_dyn + d_t_vdf / dtphys
640         z_avant = sum((q_seri + ql_seri) * zmasse, dim=2)         z_avant = sum((q_seri + ql_seri) * zmasse, dim=2)
641         CALL conflx(dtphys, paprs, play, t_seri(:, llm:1:- 1), &         CALL conflx(paprs, play, t_seri(:, llm:1:- 1), q_seri(:, llm:1:- 1), &
642              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, &
643              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, &
644              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)  
645         WHERE (rain_con < 0.) rain_con = 0.         WHERE (rain_con < 0.) rain_con = 0.
646         WHERE (snow_con < 0.) snow_con = 0.         WHERE (snow_con < 0.) snow_con = 0.
647         ibas_con = llm + 1 - kcbot         ibas_con = llm + 1 - kcbot
# Line 754  contains Line 684  contains
684         t_seri = t_seri + d_t_ajs         t_seri = t_seri + d_t_ajs
685         q_seri = q_seri + d_q_ajs         q_seri = q_seri + d_q_ajs
686      else      else
687         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, &
688              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)
689      endif      endif
690    
691      ! Caclul des ratqs      ! Caclul des ratqs
692    
     ! ratqs convectifs \`a l'ancienne en fonction de (q(z = 0) - q) / q  
     ! on \'ecrase le tableau ratqsc calcul\'e par clouds_gno  
693      if (iflag_cldcon == 1) then      if (iflag_cldcon == 1) then
694           ! ratqs convectifs \`a l'ancienne en fonction de (q(z = 0) - q) / q
695           ! on \'ecrase le tableau ratqsc calcul\'e par clouds_gno
696         do k = 1, llm         do k = 1, llm
697            do i = 1, klon            do i = 1, klon
698               if(ptconv(i, k)) then               if(ptconv(i, k)) then
# Line 796  contains Line 726  contains
726         ratqs = ratqss         ratqs = ratqss
727      endif      endif
728    
729      CALL fisrtilp(dtphys, paprs, play, t_seri, q_seri, ptconv, ratqs, &      CALL fisrtilp(paprs, play, t_seri, q_seri, ptconv, ratqs, d_t_lsc, &
730           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, &
731           pfrac_impa, pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, &           pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, psfl, rhcl)
          psfl, rhcl)  
732    
733      WHERE (rain_lsc < 0) rain_lsc = 0.      WHERE (rain_lsc < 0) rain_lsc = 0.
734      WHERE (snow_lsc < 0) snow_lsc = 0.      WHERE (snow_lsc < 0) snow_lsc = 0.
# Line 899  contains Line 828  contains
828         ENDDO         ENDDO
829      ENDDO      ENDDO
830    
     ! Introduce the aerosol direct and first indirect radiative forcings:  
     tau_ae = 0.  
     piz_ae = 0.  
     cg_ae = 0.  
   
831      ! Param\`etres optiques des nuages et quelques param\`etres pour      ! Param\`etres optiques des nuages et quelques param\`etres pour
832      ! diagnostics :      ! diagnostics :
833      if (ok_newmicro) then      if (ok_newmicro) then
834         CALL newmicro(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, &         CALL newmicro(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, &
835              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)  
836      else      else
837         CALL nuage(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, cldh, &         CALL nuage(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, cldh, &
838              cldl, cldm, cldt, cldq, ok_aie, sulfate, sulfate_pi, bl95_b0, &              cldl, cldm, cldt, cldq)
             bl95_b1, cldtaupi, re, fl)  
839      endif      endif
840    
841      IF (MOD(itap - 1, radpas) == 0) THEN      IF (MOD(itap - 1, radpas) == 0) THEN
        ! Prescrire l'ozone :  
842         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  
843         albsol = sum(falbe * pctsrf, dim = 2)         albsol = sum(falbe * pctsrf, dim = 2)
844           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, &  
845              q_seri, wo, cldfra, cldemi, cldtau, heat, heat0, cool, cool0, &              q_seri, wo, cldfra, cldemi, cldtau, heat, heat0, cool, cool0, &
846              radsol, albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, &              radsol, albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, &
847              toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, &              toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, &
848              swup0, swup, ok_ade, ok_aie, tau_ae, piz_ae, cg_ae, topswad, &              swup0, swup, ok_ade, topswad, solswad)
             solswad, cldtaupi, topswai, solswai)  
849      ENDIF      ENDIF
850    
851      ! Ajouter la tendance des rayonnements (tous les pas)      ! Ajouter la tendance des rayonnements (tous les pas)
# Line 941  contains Line 856  contains
856         ENDDO         ENDDO
857      ENDDO      ENDDO
858    
     ! Calculer l'hydrologie de la surface  
     zxqsurf = sum(fqsurf * pctsrf, dim = 2)  
     zxsnow = sum(fsnow * pctsrf, dim = 2)  
   
859      ! 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)
860      DO i = 1, klon      DO i = 1, klon
861         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)
# Line 954  contains Line 865  contains
865    
866      IF (ok_orodr) THEN      IF (ok_orodr) THEN
867         ! S\'election des points pour lesquels le sch\'ema est actif :         ! S\'election des points pour lesquels le sch\'ema est actif :
        igwd = 0  
868         DO i = 1, klon         DO i = 1, klon
869            itest(i) = 0            ktest(i) = 0
870            IF (zpic(i) - zmea(i) > 100. .AND. zstd(i) > 10.) THEN            IF (zpic(i) - zmea(i) > 100. .AND. zstd(i) > 10.) THEN
871               itest(i) = 1               ktest(i) = 1
              igwd = igwd + 1  
872            ENDIF            ENDIF
873         ENDDO         ENDDO
874    
875         CALL drag_noro(klon, llm, dtphys, paprs, play, zmea, zstd, zsig, zgam, &         CALL drag_noro(paprs, play, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
876              zthe, zpic, zval, itest, t_seri, u_seri, v_seri, zulow, zvlow, &              ktest, t_seri, u_seri, v_seri, zulow, zvlow, zustrdr, zvstrdr, &
877              zustrdr, zvstrdr, d_t_oro, d_u_oro, d_v_oro)              d_t_oro, d_u_oro, d_v_oro)
878    
879         ! ajout des tendances         ! ajout des tendances
880         DO k = 1, llm         DO k = 1, llm
# Line 979  contains Line 888  contains
888    
889      IF (ok_orolf) THEN      IF (ok_orolf) THEN
890         ! S\'election des points pour lesquels le sch\'ema est actif :         ! S\'election des points pour lesquels le sch\'ema est actif :
        igwd = 0  
891         DO i = 1, klon         DO i = 1, klon
892            itest(i) = 0            ktest(i) = 0
893            IF (zpic(i) - zmea(i) > 100.) THEN            IF (zpic(i) - zmea(i) > 100.) THEN
894               itest(i) = 1               ktest(i) = 1
              igwd = igwd + 1  
895            ENDIF            ENDIF
896         ENDDO         ENDDO
897    
898         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, &
899              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)  
900    
901         ! Ajout des tendances :         ! Ajout des tendances :
902         DO k = 1, llm         DO k = 1, llm
# Line 1002  contains Line 908  contains
908         ENDDO         ENDDO
909      ENDIF      ENDIF
910    
911      ! Stress n\'ecessaires : toute la physique      CALL aaam_bud(rg, romega, pphis, zustrdr, zustrli, &
912             sum((u_seri - u) / dtphys * zmasse, dim = 2), zvstrdr, &
913      DO i = 1, klon           zvstrli, sum((v_seri - v) / dtphys * zmasse, dim = 2), paprs, u, v, &
914         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)  
915    
916      ! Calcul des tendances traceurs      ! Calcul des tendances traceurs
917      call phytrac(julien, time, firstcal, lafin, dtphys, t, paprs, play, mfu, &      call phytrac(julien, time, firstcal, lafin, t, paprs, play, mfu, mfd, &
918           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), &
919           pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, tr_seri, &           ftsol, pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, &
920           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)  
921    
922      ! Calculer le transport de l'eau et de l'energie (diagnostique)      ! Calculer le transport de l'eau et de l'energie (diagnostique)
923      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 1094  contains Line 983  contains
983      CALL histwrite_phy("precip", rain_fall + snow_fall)      CALL histwrite_phy("precip", rain_fall + snow_fall)
984      CALL histwrite_phy("plul", rain_lsc + snow_lsc)      CALL histwrite_phy("plul", rain_lsc + snow_lsc)
985      CALL histwrite_phy("pluc", rain_con + snow_con)      CALL histwrite_phy("pluc", rain_con + snow_con)
986      CALL histwrite_phy("tsol", ztsol)      CALL histwrite_phy("tsol", tsol)
987      CALL histwrite_phy("t2m", zt2m)      CALL histwrite_phy("t2m", zt2m)
988      CALL histwrite_phy("q2m", zq2m)      CALL histwrite_phy("q2m", zq2m)
989      CALL histwrite_phy("u10m", zu10m)      CALL histwrite_phy("u10m", u10m)
990      CALL histwrite_phy("v10m", zv10m)      CALL histwrite_phy("v10m", v10m)
991      CALL histwrite_phy("snow", snow_fall)      CALL histwrite_phy("snow", snow_fall)
992      CALL histwrite_phy("cdrm", cdragm)      CALL histwrite_phy("cdrm", cdragm)
993      CALL histwrite_phy("cdrh", cdragh)      CALL histwrite_phy("cdrh", cdragh)
# Line 1114  contains Line 1003  contains
1003      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))
1004      CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))      CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))
1005      CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))      CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))
1006        CALL histwrite_phy("zxfqcalving", sum(fqcalving * pctsrf, dim = 2))
1007    
1008      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
1009         CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)         CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)
# Line 1125  contains Line 1015  contains
1015         CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))         CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))
1016         CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))         CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))
1017         CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))         CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))
1018           CALL histwrite_phy("u10m_"//clnsurf(nsrf), u10m_srf(:, nsrf))
1019           CALL histwrite_phy("v10m_"//clnsurf(nsrf), v10m_srf(:, nsrf))
1020      END DO      END DO
1021    
1022      CALL histwrite_phy("albs", albsol)      CALL histwrite_phy("albs", albsol)
# Line 1137  contains Line 1029  contains
1029      CALL histwrite_phy("s_oliqCL", s_oliqCL)      CALL histwrite_phy("s_oliqCL", s_oliqCL)
1030      CALL histwrite_phy("s_cteiCL", s_cteiCL)      CALL histwrite_phy("s_cteiCL", s_cteiCL)
1031      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)  
1032    
1033      if (conv_emanuel) then      if (conv_emanuel) then
1034         CALL histwrite_phy("ptop", ema_pct)         CALL histwrite_phy("ptop", ema_pct)
# Line 1157  contains Line 1046  contains
1046      CALL histwrite_phy("d_t_ec", d_t_ec)      CALL histwrite_phy("d_t_ec", d_t_ec)
1047      CALL histwrite_phy("dtsw0", heat0 / 86400.)      CALL histwrite_phy("dtsw0", heat0 / 86400.)
1048      CALL histwrite_phy("dtlw0", - cool0 / 86400.)      CALL histwrite_phy("dtlw0", - cool0 / 86400.)
1049        CALL histwrite_phy("msnow", sum(fsnow * pctsrf, dim = 2))
1050        call histwrite_phy("qsurf", sum(fqsurf * pctsrf, dim = 2))
1051    
1052      if (ok_instan) call histsync(nid_ins)      if (ok_instan) call histsync(nid_ins)
1053    
1054      IF (lafin) then      IF (lafin) then
1055         call NF95_CLOSE(ncid_startphy)         call NF95_CLOSE(ncid_startphy)
1056         CALL phyredem(pctsrf, ftsol, ftsoil, fqsurf, qsol, &         CALL phyredem(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, &
1057              fsnow, falbe, fevap, rain_fall, snow_fall, solsw, sollw, dlw, &              rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, agesno, &
1058              radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &              zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, &
1059              t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, &              rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
             w01)  
1060      end IF      end IF
1061    
1062      firstcal = .FALSE.      firstcal = .FALSE.

Legend:
Removed from v.214  
changed lines
  Added in v.305

  ViewVC Help
Powered by ViewVC 1.1.21