/[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 223 by guez, Fri Apr 28 13:22:36 2017 UTC trunk/phylmd/physiq.f revision 301 by guez, Thu Aug 2 17:23:07 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
# 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 170  contains Line 170  contains
170      REAL, save:: zval(klon) ! Minimum de l'OESM      REAL, save:: zval(klon) ! Minimum de l'OESM
171      REAL, save:: rugoro(klon) ! longueur de rugosite de l'OESM      REAL, save:: rugoro(klon) ! longueur de rugosite de l'OESM
172      REAL zulow(klon), zvlow(klon)      REAL zulow(klon), zvlow(klon)
173      INTEGER igwd, itest(klon)      INTEGER ktest(klon)
174    
175      REAL, save:: agesno(klon, nbsrf) ! age de la neige      REAL, save:: agesno(klon, nbsrf) ! age de la neige
176      REAL, save:: run_off_lic_0(klon)      REAL, save:: run_off_lic_0(klon)
177    
178      ! Variables li\'ees \`a la convection d'Emanuel :      ! Variables li\'ees \`a la convection d'Emanuel :
179      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  
180      REAL, save:: sig1(klon, llm), w01(klon, llm)      REAL, save:: sig1(klon, llm), w01(klon, llm)
181    
182      ! Variables pour la couche limite (Alain Lahellec) :      ! Variables pour la couche limite (Alain Lahellec) :
183      REAL cdragh(klon) ! drag coefficient pour T and Q      REAL cdragh(klon) ! drag coefficient pour T and Q
184      REAL cdragm(klon) ! drag coefficient pour vent      REAL cdragm(klon) ! drag coefficient pour vent
185    
186      ! 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  
187    
188      REAL, save:: ffonte(klon, nbsrf)      REAL, save:: ffonte(klon, nbsrf)
189      ! flux thermique utilise pour fondre la neige      ! flux thermique utilise pour fondre la neige
190    
191      REAL, save:: fqcalving(klon, nbsrf)      REAL fqcalving(klon, nbsrf)
192      ! flux d'eau "perdue" par la surface et necessaire pour limiter la      ! flux d'eau "perdue" par la surface et n\'ecessaire pour limiter
193      ! hauteur de neige, en kg / m2 / s      ! la hauteur de neige, en kg / m2 / s
194    
195      REAL zxffonte(klon), zxfqcalving(klon)      REAL zxffonte(klon)
196    
197      REAL, save:: pfrac_impa(klon, llm)! Produits des coefs lessivage impaction      REAL, save:: pfrac_impa(klon, llm)! Produits des coefs lessivage impaction
198      REAL, save:: pfrac_nucl(klon, llm)! Produits des coefs lessivage nucleation      REAL, save:: pfrac_nucl(klon, llm)! Produits des coefs lessivage nucleation
# Line 241  contains Line 237  contains
237      real, save:: clwcon(klon, llm), rnebcon(klon, llm)      real, save:: clwcon(klon, llm), rnebcon(klon, llm)
238      real, save:: clwcon0(klon, llm), rnebcon0(klon, llm)      real, save:: clwcon0(klon, llm), rnebcon0(klon, llm)
239    
240      REAL rhcl(klon, llm) ! humiditi relative ciel clair      REAL rhcl(klon, llm) ! humidit\'e relative ciel clair
241      REAL dialiq(klon, llm) ! eau liquide nuageuse      REAL dialiq(klon, llm) ! eau liquide nuageuse
242      REAL diafra(klon, llm) ! fraction nuageuse      REAL diafra(klon, llm) ! fraction nuageuse
243      REAL cldliq(klon, llm) ! eau liquide nuageuse      REAL cldliq(klon, llm) ! eau liquide nuageuse
# Line 251  contains Line 247  contains
247    
248      REAL flux_q(klon, nbsrf) ! flux turbulent d'humidite à la surface      REAL flux_q(klon, nbsrf) ! flux turbulent d'humidite à la surface
249      REAL flux_t(klon, nbsrf) ! flux turbulent de chaleur à la surface      REAL flux_t(klon, nbsrf) ! flux turbulent de chaleur à la surface
250      REAL flux_u(klon, nbsrf) ! flux turbulent de vitesse u à la surface  
251      REAL flux_v(klon, nbsrf) ! flux turbulent de vitesse v à la surface      REAL flux_u(klon, nbsrf), flux_v(klon, nbsrf)
252        ! tension du vent (flux turbulent de vent) à la surface, en Pa
253    
254      ! 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
255      ! les variables soient r\'emanentes.      ! les variables soient r\'emanentes.
# Line 293  contains Line 290  contains
290      REAL, SAVE:: cteiCL(klon, nbsrf) ! cloud top instab. crit. couche limite      REAL, SAVE:: cteiCL(klon, nbsrf) ! cloud top instab. crit. couche limite
291      REAL, SAVE:: pblt(klon, nbsrf) ! T \`a la hauteur de couche limite      REAL, SAVE:: pblt(klon, nbsrf) ! T \`a la hauteur de couche limite
292      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  
293      ! Grandeurs de sorties      ! Grandeurs de sorties
294      REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)      REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)
295      REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)      REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)
296      REAL s_therm(klon), s_trmb1(klon), s_trmb2(klon)      REAL s_therm(klon)
     REAL s_trmb3(klon)  
297    
298      ! Variables pour la convection de K. Emanuel :      ! Variables pour la convection de K. Emanuel :
299    
# Line 372  contains Line 365  contains
365    
366      REAL zustrdr(klon), zvstrdr(klon)      REAL zustrdr(klon), zvstrdr(klon)
367      REAL zustrli(klon), zvstrli(klon)      REAL zustrli(klon), zvstrli(klon)
     REAL zustrph(klon), zvstrph(klon)  
368      REAL aam, torsfc      REAL aam, torsfc
369    
370      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 380  contains Line 372  contains
372      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.
373      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.
374    
     real date0  
375      REAL tsol(klon)      REAL tsol(klon)
376    
377      REAL d_t_ec(klon, llm)      REAL d_t_ec(klon, llm)
# Line 390  contains Line 381  contains
381      REAL, save:: t2m(klon, nbsrf), q2m(klon, nbsrf)      REAL, save:: t2m(klon, nbsrf), q2m(klon, nbsrf)
382      ! temperature and humidity at 2 m      ! temperature and humidity at 2 m
383    
384      REAL, save:: u10m(klon, nbsrf), v10m(klon, nbsrf) ! vents a 10 m      REAL, save:: u10m_srf(klon, nbsrf), v10m_srf(klon, nbsrf)
385        ! composantes du vent \`a 10 m
386        
387      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
388      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
389    
390      ! Aerosol effects:      ! Aerosol effects:
391    
# Line 420  contains Line 413  contains
413    
414      test_firstcal: IF (firstcal) THEN      test_firstcal: IF (firstcal) THEN
415         ! initialiser         ! initialiser
416         u10m = 0.         u10m_srf = 0.
417         v10m = 0.         v10m_srf = 0.
418         t2m = 0.         t2m = 0.
419         q2m = 0.         q2m = 0.
420         ffonte = 0.         ffonte = 0.
        fqcalving = 0.  
421         rain_con = 0.         rain_con = 0.
422         snow_con = 0.         snow_con = 0.
423         d_u_con = 0.         d_u_con = 0.
# Line 441  contains Line 433  contains
433         cteiCL =0. ! cloud top instab. crit. couche limite         cteiCL =0. ! cloud top instab. crit. couche limite
434         pblt =0.         pblt =0.
435         therm =0.         therm =0.
        trmb1 =0. ! deep_cape  
        trmb2 =0. ! inhibition  
        trmb3 =0. ! Point Omega  
436    
437         iflag_thermals = 0         iflag_thermals = 0
438         nsplit_thermals = 1         nsplit_thermals = 1
# Line 481  contains Line 470  contains
470            rugoro = 0.            rugoro = 0.
471         ENDIF         ENDIF
472    
        ecrit_ins = NINT(ecrit_ins / dtphys)  
   
473         ! Initialisation des sorties         ! Initialisation des sorties
474           call ini_histins(ok_newmicro)
        call ini_histins(dtphys, ok_newmicro)  
        CALL ymds2ju(annee_ref, 1, day_ref, 0., date0)  
        ! Positionner date0 pour initialisation de ORCHIDEE  
        print *, 'physiq date0: ', date0  
475         CALL phyredem0         CALL phyredem0
476           call conf_interface
477      ENDIF test_firstcal      ENDIF test_firstcal
478    
479      ! We will modify variables *_seri and we will not touch variables      ! We will modify variables *_seri and we will not touch variables
# Line 567  contains Line 551  contains
551         fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)         fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)
552      END forall      END forall
553    
554      CALL clmain(dtphys, pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &      CALL pbl_surface(pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &
555           ftsol, cdmmax, cdhmax, ksta, ksta_ter, ok_kzmin, ftsoil, qsol, &           ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, &
556           paprs, play, fsnow, fqsurf, fevap, falbe, fluxlat, rain_fall, &           fevap, falbe, fluxlat, rain_fall, snow_fall, fsolsw, fsollw, frugs, &
557           snow_fall, fsolsw, fsollw, frugs, agesno, rugoro, d_t_vdf, d_q_vdf, &           agesno, rugoro, d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, &
558           d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, flux_u, flux_v, cdragh, &           flux_q, flux_u, flux_v, cdragh, cdragm, q2, dsens, devap, coefh, t2m, &
559           cdragm, q2, dsens, devap, ycoefh, yu1, yv1, t2m, q2m, u10m, v10m, &           q2m, u10m_srf, v10m_srf, pblh, capCL, oliqCL, cteiCL, pblT, therm, &
560           pblh, capCL, oliqCL, cteiCL, pblT, therm, trmb1, trmb2, trmb3, plcl, &           plcl, fqcalving, ffonte, run_off_lic_0)
          fqcalving, ffonte, run_off_lic_0)  
561    
562      ! Incr\'ementation des flux      ! Incr\'ementation des flux
563    
# Line 599  contains Line 582  contains
582      zxfluxlat = sum(fluxlat * pctsrf, dim = 2)      zxfluxlat = sum(fluxlat * pctsrf, dim = 2)
583      zt2m = sum(t2m * pctsrf, dim = 2)      zt2m = sum(t2m * pctsrf, dim = 2)
584      zq2m = sum(q2m * pctsrf, dim = 2)      zq2m = sum(q2m * pctsrf, dim = 2)
585      zu10m = sum(u10m * pctsrf, dim = 2)      u10m = sum(u10m_srf * pctsrf, dim = 2)
586      zv10m = sum(v10m * pctsrf, dim = 2)      v10m = sum(v10m_srf * pctsrf, dim = 2)
587      zxffonte = sum(ffonte * pctsrf, dim = 2)      zxffonte = sum(ffonte * pctsrf, dim = 2)
     zxfqcalving = sum(fqcalving * pctsrf, dim = 2)  
588      s_pblh = sum(pblh * pctsrf, dim = 2)      s_pblh = sum(pblh * pctsrf, dim = 2)
589      s_lcl = sum(plcl * pctsrf, dim = 2)      s_lcl = sum(plcl * pctsrf, dim = 2)
590      s_capCL = sum(capCL * pctsrf, dim = 2)      s_capCL = sum(capCL * pctsrf, dim = 2)
# Line 610  contains Line 592  contains
592      s_cteiCL = sum(cteiCL * pctsrf, dim = 2)      s_cteiCL = sum(cteiCL * pctsrf, dim = 2)
593      s_pblT = sum(pblT * pctsrf, dim = 2)      s_pblT = sum(pblT * pctsrf, dim = 2)
594      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)  
595    
596      ! Si une sous-fraction n'existe pas, elle prend la valeur moyenne :      ! Si une sous-fraction n'existe pas, elle prend la valeur moyenne :
597      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
# Line 621  contains Line 600  contains
600               ftsol(i, nsrf) = tsol(i)               ftsol(i, nsrf) = tsol(i)
601               t2m(i, nsrf) = zt2m(i)               t2m(i, nsrf) = zt2m(i)
602               q2m(i, nsrf) = zq2m(i)               q2m(i, nsrf) = zq2m(i)
603               u10m(i, nsrf) = zu10m(i)               u10m_srf(i, nsrf) = u10m(i)
604               v10m(i, nsrf) = zv10m(i)               v10m_srf(i, nsrf) = v10m(i)
605               ffonte(i, nsrf) = zxffonte(i)               ffonte(i, nsrf) = zxffonte(i)
              fqcalving(i, nsrf) = zxfqcalving(i)  
606               pblh(i, nsrf) = s_pblh(i)               pblh(i, nsrf) = s_pblh(i)
607               plcl(i, nsrf) = s_lcl(i)               plcl(i, nsrf) = s_lcl(i)
608               capCL(i, nsrf) = s_capCL(i)               capCL(i, nsrf) = s_capCL(i)
# Line 632  contains Line 610  contains
610               cteiCL(i, nsrf) = s_cteiCL(i)               cteiCL(i, nsrf) = s_cteiCL(i)
611               pblT(i, nsrf) = s_pblT(i)               pblT(i, nsrf) = s_pblT(i)
612               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)  
613            end IF            end IF
614         ENDDO         ENDDO
615      ENDDO      ENDDO
# Line 646  contains Line 621  contains
621      if (conv_emanuel) then      if (conv_emanuel) then
622         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, &
623              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, &
624              upwd, dnwd, Ma, cape, iflagctrl, qcondc, pmflxr, da, phi, mp)              upwd, dnwd, Ma, cape, iflagctrl, clwcon0, pmflxr, da, phi, mp)
625         snow_con = 0.         snow_con = 0.
        clwcon0 = qcondc  
626         mfu = upwd + dnwd         mfu = upwd + dnwd
627    
628         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 669  contains Line 643  contains
643         conv_q = d_q_dyn + d_q_vdf / dtphys         conv_q = d_q_dyn + d_q_vdf / dtphys
644         conv_t = d_t_dyn + d_t_vdf / dtphys         conv_t = d_t_dyn + d_t_vdf / dtphys
645         z_avant = sum((q_seri + ql_seri) * zmasse, dim=2)         z_avant = sum((q_seri + ql_seri) * zmasse, dim=2)
646         CALL conflx(dtphys, paprs, play, t_seri(:, llm:1:- 1), &         CALL conflx(paprs, play, t_seri(:, llm:1:- 1), q_seri(:, llm:1:- 1), &
647              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, &
648              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, &
649              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)  
650         WHERE (rain_con < 0.) rain_con = 0.         WHERE (rain_con < 0.) rain_con = 0.
651         WHERE (snow_con < 0.) snow_con = 0.         WHERE (snow_con < 0.) snow_con = 0.
652         ibas_con = llm + 1 - kcbot         ibas_con = llm + 1 - kcbot
# Line 716  contains Line 689  contains
689         t_seri = t_seri + d_t_ajs         t_seri = t_seri + d_t_ajs
690         q_seri = q_seri + d_q_ajs         q_seri = q_seri + d_q_ajs
691      else      else
692         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, &
693              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)
694      endif      endif
695    
696      ! Caclul des ratqs      ! Caclul des ratqs
697    
     ! ratqs convectifs \`a l'ancienne en fonction de (q(z = 0) - q) / q  
     ! on \'ecrase le tableau ratqsc calcul\'e par clouds_gno  
698      if (iflag_cldcon == 1) then      if (iflag_cldcon == 1) then
699           ! ratqs convectifs \`a l'ancienne en fonction de (q(z = 0) - q) / q
700           ! on \'ecrase le tableau ratqsc calcul\'e par clouds_gno
701         do k = 1, llm         do k = 1, llm
702            do i = 1, klon            do i = 1, klon
703               if(ptconv(i, k)) then               if(ptconv(i, k)) then
# Line 758  contains Line 731  contains
731         ratqs = ratqss         ratqs = ratqss
732      endif      endif
733    
734      CALL fisrtilp(dtphys, paprs, play, t_seri, q_seri, ptconv, ratqs, &      CALL fisrtilp(paprs, play, t_seri, q_seri, ptconv, ratqs, d_t_lsc, &
735           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, &
736           pfrac_impa, pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, &           pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, psfl, rhcl)
          psfl, rhcl)  
737    
738      WHERE (rain_lsc < 0) rain_lsc = 0.      WHERE (rain_lsc < 0) rain_lsc = 0.
739      WHERE (snow_lsc < 0) snow_lsc = 0.      WHERE (snow_lsc < 0) snow_lsc = 0.
# Line 898  contains Line 870  contains
870    
871      IF (ok_orodr) THEN      IF (ok_orodr) THEN
872         ! S\'election des points pour lesquels le sch\'ema est actif :         ! S\'election des points pour lesquels le sch\'ema est actif :
        igwd = 0  
873         DO i = 1, klon         DO i = 1, klon
874            itest(i) = 0            ktest(i) = 0
875            IF (zpic(i) - zmea(i) > 100. .AND. zstd(i) > 10.) THEN            IF (zpic(i) - zmea(i) > 100. .AND. zstd(i) > 10.) THEN
876               itest(i) = 1               ktest(i) = 1
              igwd = igwd + 1  
877            ENDIF            ENDIF
878         ENDDO         ENDDO
879    
880         CALL drag_noro(klon, llm, dtphys, paprs, play, zmea, zstd, zsig, zgam, &         CALL drag_noro(paprs, play, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
881              zthe, zpic, zval, itest, t_seri, u_seri, v_seri, zulow, zvlow, &              ktest, t_seri, u_seri, v_seri, zulow, zvlow, zustrdr, zvstrdr, &
882              zustrdr, zvstrdr, d_t_oro, d_u_oro, d_v_oro)              d_t_oro, d_u_oro, d_v_oro)
883    
884         ! ajout des tendances         ! ajout des tendances
885         DO k = 1, llm         DO k = 1, llm
# Line 923  contains Line 893  contains
893    
894      IF (ok_orolf) THEN      IF (ok_orolf) THEN
895         ! S\'election des points pour lesquels le sch\'ema est actif :         ! S\'election des points pour lesquels le sch\'ema est actif :
        igwd = 0  
896         DO i = 1, klon         DO i = 1, klon
897            itest(i) = 0            ktest(i) = 0
898            IF (zpic(i) - zmea(i) > 100.) THEN            IF (zpic(i) - zmea(i) > 100.) THEN
899               itest(i) = 1               ktest(i) = 1
              igwd = igwd + 1  
900            ENDIF            ENDIF
901         ENDDO         ENDDO
902    
903         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, &
904              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)  
905    
906         ! Ajout des tendances :         ! Ajout des tendances :
907         DO k = 1, llm         DO k = 1, llm
# Line 946  contains Line 913  contains
913         ENDDO         ENDDO
914      ENDIF      ENDIF
915    
916      ! Stress n\'ecessaires : toute la physique      CALL aaam_bud(rg, romega, pphis, zustrdr, zustrli, &
917             sum((u_seri - u) / dtphys * zmasse, dim = 2), zvstrdr, &
918      DO i = 1, klon           zvstrli, sum((v_seri - v) / dtphys * zmasse, dim = 2), paprs, u, v, &
919         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)  
920    
921      ! Calcul des tendances traceurs      ! Calcul des tendances traceurs
922      call phytrac(julien, time, firstcal, lafin, dtphys, t, paprs, play, mfu, &      call phytrac(julien, time, firstcal, lafin, t, paprs, play, mfu, mfd, &
923           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), &
924           pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, tr_seri, &           ftsol, pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, &
925           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)  
926    
927      ! Calculer le transport de l'eau et de l'energie (diagnostique)      ! Calculer le transport de l'eau et de l'energie (diagnostique)
928      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 1041  contains Line 991  contains
991      CALL histwrite_phy("tsol", tsol)      CALL histwrite_phy("tsol", tsol)
992      CALL histwrite_phy("t2m", zt2m)      CALL histwrite_phy("t2m", zt2m)
993      CALL histwrite_phy("q2m", zq2m)      CALL histwrite_phy("q2m", zq2m)
994      CALL histwrite_phy("u10m", zu10m)      CALL histwrite_phy("u10m", u10m)
995      CALL histwrite_phy("v10m", zv10m)      CALL histwrite_phy("v10m", v10m)
996      CALL histwrite_phy("snow", snow_fall)      CALL histwrite_phy("snow", snow_fall)
997      CALL histwrite_phy("cdrm", cdragm)      CALL histwrite_phy("cdrm", cdragm)
998      CALL histwrite_phy("cdrh", cdragh)      CALL histwrite_phy("cdrh", cdragh)
# Line 1058  contains Line 1008  contains
1008      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))
1009      CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))      CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))
1010      CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))      CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))
1011        CALL histwrite_phy("zxfqcalving", sum(fqcalving * pctsrf, dim = 2))
1012    
1013      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
1014         CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)         CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)
# Line 1069  contains Line 1020  contains
1020         CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))         CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))
1021         CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))         CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))
1022         CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))         CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))
1023           CALL histwrite_phy("u10m_"//clnsurf(nsrf), u10m_srf(:, nsrf))
1024           CALL histwrite_phy("v10m_"//clnsurf(nsrf), v10m_srf(:, nsrf))
1025      END DO      END DO
1026    
1027      CALL histwrite_phy("albs", albsol)      CALL histwrite_phy("albs", albsol)
# Line 1081  contains Line 1034  contains
1034      CALL histwrite_phy("s_oliqCL", s_oliqCL)      CALL histwrite_phy("s_oliqCL", s_oliqCL)
1035      CALL histwrite_phy("s_cteiCL", s_cteiCL)      CALL histwrite_phy("s_cteiCL", s_cteiCL)
1036      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)  
1037    
1038      if (conv_emanuel) then      if (conv_emanuel) then
1039         CALL histwrite_phy("ptop", ema_pct)         CALL histwrite_phy("ptop", ema_pct)

Legend:
Removed from v.223  
changed lines
  Added in v.301

  ViewVC Help
Powered by ViewVC 1.1.21