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

Diff of /trunk/phylmd/physiq.f

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

trunk/Sources/phylmd/physiq.f revision 250 by guez, Fri Jan 5 18:18:53 2018 UTC trunk/phylmd/physiq.f revision 288 by guez, Tue Jul 24 16:27:12 2018 UTC
# Line 20  contains Line 20  contains
20      use calltherm_m, only: calltherm      use calltherm_m, only: calltherm
21      USE clesphys, ONLY: cdhmax, cdmmax, ecrit_ins, ok_instan      USE clesphys, ONLY: cdhmax, cdmmax, ecrit_ins, 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 pbl_surface_m, ONLY: pbl_surface
24      use clouds_gno_m, only: clouds_gno      use clouds_gno_m, only: clouds_gno
25      use comconst, only: dtphys      use comconst, only: dtphys
26      USE comgeomphy, ONLY: airephy      USE comgeomphy, ONLY: airephy
# Line 30  contains Line 30  contains
30      use conflx_m, only: conflx      use conflx_m, only: conflx
31      USE ctherm, ONLY: iflag_thermals, nsplit_thermals      USE ctherm, ONLY: iflag_thermals, nsplit_thermals
32      use diagcld2_m, only: diagcld2      use diagcld2_m, only: diagcld2
33      USE dimens_m, ONLY: llm, nqmx      USE dimensions, ONLY: llm, nqmx
34      USE dimphy, ONLY: klon      USE dimphy, ONLY: klon
35      USE dimsoil, ONLY: nsoilmx      USE dimsoil, ONLY: nsoilmx
36      use drag_noro_m, only: drag_noro      use drag_noro_m, only: drag_noro
# Line 176  contains Line 176  contains
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) :
# Line 188  contains Line 187  contains
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 237  contains Line 236  contains
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 290  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 376  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    
     real date0  
374      REAL tsol(klon)      REAL tsol(klon)
375    
376      REAL d_t_ec(klon, llm)      REAL d_t_ec(klon, llm)
# Line 423  contains Line 417  contains
417         t2m = 0.         t2m = 0.
418         q2m = 0.         q2m = 0.
419         ffonte = 0.         ffonte = 0.
        fqcalving = 0.  
420         rain_con = 0.         rain_con = 0.
421         snow_con = 0.         snow_con = 0.
422         d_u_con = 0.         d_u_con = 0.
# Line 439  contains Line 432  contains
432         cteiCL =0. ! cloud top instab. crit. couche limite         cteiCL =0. ! cloud top instab. crit. couche limite
433         pblt =0.         pblt =0.
434         therm =0.         therm =0.
        trmb1 =0. ! deep_cape  
        trmb2 =0. ! inhibition  
        trmb3 =0. ! Point Omega  
435    
436         iflag_thermals = 0         iflag_thermals = 0
437         nsplit_thermals = 1         nsplit_thermals = 1
# Line 479  contains Line 469  contains
469            rugoro = 0.            rugoro = 0.
470         ENDIF         ENDIF
471    
        ecrit_ins = NINT(ecrit_ins / dtphys)  
   
472         ! Initialisation des sorties         ! Initialisation des sorties
   
473         call ini_histins(dtphys, 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  
474         CALL phyredem0         CALL phyredem0
475      ENDIF test_firstcal      ENDIF test_firstcal
476    
# Line 565  contains Line 549  contains
549         fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)         fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)
550      END forall      END forall
551    
552      CALL clmain(dtphys, pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &      CALL pbl_surface(dtphys, pctsrf, t_seri, q_seri, u_seri, v_seri, julien, &
553           ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, &           mu0, ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, &
554           fevap, falbe, fluxlat, rain_fall, snow_fall, fsolsw, fsollw, frugs, &           fevap, falbe, fluxlat, rain_fall, snow_fall, fsolsw, fsollw, frugs, &
555           agesno, rugoro, d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, &           agesno, rugoro, d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, &
556           flux_q, flux_u, flux_v, cdragh, cdragm, q2, dsens, devap, coefh, t2m, &           flux_q, flux_u, flux_v, cdragh, cdragm, q2, dsens, devap, coefh, t2m, &
557           q2m, u10m_srf, v10m_srf, pblh, capCL, oliqCL, cteiCL, pblT, therm, &           q2m, u10m_srf, v10m_srf, pblh, capCL, oliqCL, cteiCL, pblT, therm, &
558           trmb1, trmb2, trmb3, plcl, fqcalving, ffonte, run_off_lic_0)           plcl, fqcalving, ffonte, run_off_lic_0)
559    
560      ! Incr\'ementation des flux      ! Incr\'ementation des flux
561    
# Line 599  contains Line 583  contains
583      u10m = sum(u10m_srf * pctsrf, dim = 2)      u10m = sum(u10m_srf * pctsrf, dim = 2)
584      v10m = sum(v10m_srf * pctsrf, dim = 2)      v10m = sum(v10m_srf * pctsrf, dim = 2)
585      zxffonte = sum(ffonte * pctsrf, dim = 2)      zxffonte = sum(ffonte * pctsrf, dim = 2)
     zxfqcalving = sum(fqcalving * pctsrf, dim = 2)  
586      s_pblh = sum(pblh * pctsrf, dim = 2)      s_pblh = sum(pblh * pctsrf, dim = 2)
587      s_lcl = sum(plcl * pctsrf, dim = 2)      s_lcl = sum(plcl * pctsrf, dim = 2)
588      s_capCL = sum(capCL * pctsrf, dim = 2)      s_capCL = sum(capCL * pctsrf, dim = 2)
# Line 607  contains Line 590  contains
590      s_cteiCL = sum(cteiCL * pctsrf, dim = 2)      s_cteiCL = sum(cteiCL * pctsrf, dim = 2)
591      s_pblT = sum(pblT * pctsrf, dim = 2)      s_pblT = sum(pblT * pctsrf, dim = 2)
592      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)  
593    
594      ! Si une sous-fraction n'existe pas, elle prend la valeur moyenne :      ! Si une sous-fraction n'existe pas, elle prend la valeur moyenne :
595      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
# Line 621  contains Line 601  contains
601               u10m_srf(i, nsrf) = u10m(i)               u10m_srf(i, nsrf) = u10m(i)
602               v10m_srf(i, nsrf) = v10m(i)               v10m_srf(i, nsrf) = v10m(i)
603               ffonte(i, nsrf) = zxffonte(i)               ffonte(i, nsrf) = zxffonte(i)
              fqcalving(i, nsrf) = zxfqcalving(i)  
604               pblh(i, nsrf) = s_pblh(i)               pblh(i, nsrf) = s_pblh(i)
605               plcl(i, nsrf) = s_lcl(i)               plcl(i, nsrf) = s_lcl(i)
606               capCL(i, nsrf) = s_capCL(i)               capCL(i, nsrf) = s_capCL(i)
# Line 629  contains Line 608  contains
608               cteiCL(i, nsrf) = s_cteiCL(i)               cteiCL(i, nsrf) = s_cteiCL(i)
609               pblT(i, nsrf) = s_pblT(i)               pblT(i, nsrf) = s_pblT(i)
610               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)  
611            end IF            end IF
612         ENDDO         ENDDO
613      ENDDO      ENDDO
# Line 643  contains Line 619  contains
619      if (conv_emanuel) then      if (conv_emanuel) then
620         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, &
621              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, &
622              upwd, dnwd, Ma, cape, iflagctrl, qcondc, pmflxr, da, phi, mp)              upwd, dnwd, Ma, cape, iflagctrl, clwcon0, pmflxr, da, phi, mp)
623         snow_con = 0.         snow_con = 0.
        clwcon0 = qcondc  
624         mfu = upwd + dnwd         mfu = upwd + dnwd
625    
626         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 667  contains Line 642  contains
642         conv_t = d_t_dyn + d_t_vdf / dtphys         conv_t = d_t_dyn + d_t_vdf / dtphys
643         z_avant = sum((q_seri + ql_seri) * zmasse, dim=2)         z_avant = sum((q_seri + ql_seri) * zmasse, dim=2)
644         CALL conflx(dtphys, paprs, play, t_seri(:, llm:1:- 1), &         CALL conflx(dtphys, paprs, play, t_seri(:, llm:1:- 1), &
645              q_seri(:, llm:1:- 1), conv_t, conv_q, - evap, omega, &              q_seri(:, llm:1:- 1), conv_t, conv_q, - evap, omega, d_t_con, &
646              d_t_con, d_q_con, rain_con, snow_con, mfu(:, llm:1:- 1), &              d_q_con, rain_con, snow_con, mfu(:, llm:1:- 1), mfd(:, llm:1:- 1), &
647              mfd(:, llm:1:- 1), pen_u, pde_u, pen_d, pde_d, kcbot, kctop, &              pen_u, pde_u, pen_d, pde_d, kcbot, kctop, kdtop, pmflxr, pmflxs)
             kdtop, pmflxr, pmflxs)  
648         WHERE (rain_con < 0.) rain_con = 0.         WHERE (rain_con < 0.) rain_con = 0.
649         WHERE (snow_con < 0.) snow_con = 0.         WHERE (snow_con < 0.) snow_con = 0.
650         ibas_con = llm + 1 - kcbot         ibas_con = llm + 1 - kcbot
# Line 719  contains Line 693  contains
693    
694      ! Caclul des ratqs      ! Caclul des ratqs
695    
     ! ratqs convectifs \`a l'ancienne en fonction de (q(z = 0) - q) / q  
     ! on \'ecrase le tableau ratqsc calcul\'e par clouds_gno  
696      if (iflag_cldcon == 1) then      if (iflag_cldcon == 1) then
697           ! ratqs convectifs \`a l'ancienne en fonction de (q(z = 0) - q) / q
698           ! on \'ecrase le tableau ratqsc calcul\'e par clouds_gno
699         do k = 1, llm         do k = 1, llm
700            do i = 1, klon            do i = 1, klon
701               if(ptconv(i, k)) then               if(ptconv(i, k)) then
# Line 755  contains Line 729  contains
729         ratqs = ratqss         ratqs = ratqss
730      endif      endif
731    
732      CALL fisrtilp(dtphys, paprs, play, t_seri, q_seri, ptconv, ratqs, &      CALL fisrtilp(dtphys, paprs, play, t_seri, q_seri, ptconv, ratqs, d_t_lsc, &
733           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, &
734           pfrac_impa, pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, &           pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, psfl, rhcl)
          psfl, rhcl)  
735    
736      WHERE (rain_lsc < 0) rain_lsc = 0.      WHERE (rain_lsc < 0) rain_lsc = 0.
737      WHERE (snow_lsc < 0) snow_lsc = 0.      WHERE (snow_lsc < 0) snow_lsc = 0.
# Line 1034  contains Line 1007  contains
1007      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))
1008      CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))      CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))
1009      CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))      CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))
1010        CALL histwrite_phy("zxfqcalving", sum(fqcalving * pctsrf, dim = 2))
1011    
1012      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
1013         CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)         CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)
# Line 1059  contains Line 1033  contains
1033      CALL histwrite_phy("s_oliqCL", s_oliqCL)      CALL histwrite_phy("s_oliqCL", s_oliqCL)
1034      CALL histwrite_phy("s_cteiCL", s_cteiCL)      CALL histwrite_phy("s_cteiCL", s_cteiCL)
1035      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)  
1036    
1037      if (conv_emanuel) then      if (conv_emanuel) then
1038         CALL histwrite_phy("ptop", ema_pct)         CALL histwrite_phy("ptop", ema_pct)

Legend:
Removed from v.250  
changed lines
  Added in v.288

  ViewVC Help
Powered by ViewVC 1.1.21