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

Diff of /trunk/phylmd/physiq.f90

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

revision 298 by guez, Thu Jul 26 16:45:51 2018 UTC revision 306 by guez, Tue Sep 11 12:23:47 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 conf_interface_m, ONLY: conf_interface
24      USE pbl_surface_m, ONLY: pbl_surface      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
# Line 149  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)
# Line 211  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) ! derivative of infra-red flux      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 fder(klon) ! Derive de flux (sensible et latente)      REAL fder(klon) ! Derive de flux (sensible et latente)
# Line 326  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) ! variation of ftsol      REAL d_ts(klon, nbsrf) ! variation of ftsol
334    
# Line 417  contains Line 417  contains
417         t2m = 0.         t2m = 0.
418         q2m = 0.         q2m = 0.
419         ffonte = 0.         ffonte = 0.
        rain_con = 0.  
        snow_con = 0.  
420         d_u_con = 0.         d_u_con = 0.
421         d_v_con = 0.         d_v_con = 0.
422         rnebcon0 = 0.         rnebcon0 = 0.
# Line 445  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 472  contains Line 470  contains
470         ! Initialisation des sorties         ! Initialisation des sorties
471         call ini_histins(ok_newmicro)         call ini_histins(ok_newmicro)
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 551  contains Line 550  contains
550    
551      CALL pbl_surface(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, &
552           ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, &           ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, &
553           fevap, falbe, fluxlat, rain_fall, snow_fall, fsolsw, fsollw, frugs, &           falbe, fluxlat, rain_fall, snow_fall, fsolsw, fsollw, frugs, agesno, &
554           agesno, rugoro, d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, &           rugoro, d_t_vdf, d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, &
555           flux_q, flux_u, flux_v, cdragh, cdragm, q2, dsens, devap, coefh, t2m, &           flux_u, flux_v, cdragh, cdragm, q2, dflux_t, dflux_q, coefh, t2m, &
556           q2m, u10m_srf, v10m_srf, pblh, capCL, oliqCL, cteiCL, pblT, therm, &           q2m, u10m_srf, v10m_srf, pblh, capCL, oliqCL, cteiCL, pblT, therm, &
557           plcl, fqcalving, ffonte, run_off_lic_0)           plcl, fqcalving, ffonte, run_off_lic_0)
558    
# Line 561  contains Line 560  contains
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 572  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      tsol = 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)
# Line 1007  contains Line 1004  contains
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))      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))  
        CALL histwrite_phy("u10m_"//clnsurf(nsrf), u10m_srf(:, nsrf))  
        CALL histwrite_phy("v10m_"//clnsurf(nsrf), v10m_srf(:, nsrf))  
     END DO  
   
1007      CALL histwrite_phy("albs", albsol)      CALL histwrite_phy("albs", albsol)
1008      CALL histwrite_phy("tro3", wo * dobson_u * 1e3 / zmasse / rmo3 * md)      CALL histwrite_phy("tro3", wo * dobson_u * 1e3 / zmasse / rmo3 * md)
1009      CALL histwrite_phy("rugs", zxrugs)      CALL histwrite_phy("rugs", zxrugs)
# Line 1032  contains Line 1014  contains
1014      CALL histwrite_phy("s_oliqCL", s_oliqCL)      CALL histwrite_phy("s_oliqCL", s_oliqCL)
1015      CALL histwrite_phy("s_cteiCL", s_cteiCL)      CALL histwrite_phy("s_cteiCL", s_cteiCL)
1016      CALL histwrite_phy("s_therm", s_therm)      CALL histwrite_phy("s_therm", s_therm)
   
     if (conv_emanuel) then  
        CALL histwrite_phy("ptop", ema_pct)  
        CALL histwrite_phy("dnwd0", - mp)  
     end if  
   
1017      CALL histwrite_phy("temp", t_seri)      CALL histwrite_phy("temp", t_seri)
1018      CALL histwrite_phy("vitu", u_seri)      CALL histwrite_phy("vitu", u_seri)
1019      CALL histwrite_phy("vitv", v_seri)      CALL histwrite_phy("vitv", v_seri)
# Line 1051  contains Line 1027  contains
1027      CALL histwrite_phy("dtlw0", - cool0 / 86400.)      CALL histwrite_phy("dtlw0", - cool0 / 86400.)
1028      CALL histwrite_phy("msnow", sum(fsnow * pctsrf, dim = 2))      CALL histwrite_phy("msnow", sum(fsnow * pctsrf, dim = 2))
1029      call histwrite_phy("qsurf", sum(fqsurf * pctsrf, dim = 2))      call histwrite_phy("qsurf", sum(fqsurf * pctsrf, dim = 2))
1030        call histwrite_phy("flat", zxfluxlat)
1031    
1032        DO nsrf = 1, nbsrf
1033           CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)
1034           CALL histwrite_phy("fract_"//clnsurf(nsrf), pctsrf(:, nsrf))
1035           CALL histwrite_phy("sens_"//clnsurf(nsrf), flux_t(:, nsrf))
1036           CALL histwrite_phy("lat_"//clnsurf(nsrf), fluxlat(:, nsrf))
1037           CALL histwrite_phy("tsol_"//clnsurf(nsrf), ftsol(:, nsrf))
1038           CALL histwrite_phy("taux_"//clnsurf(nsrf), flux_u(:, nsrf))
1039           CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))
1040           CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))
1041           CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))
1042           CALL histwrite_phy("u10m_"//clnsurf(nsrf), u10m_srf(:, nsrf))
1043           CALL histwrite_phy("v10m_"//clnsurf(nsrf), v10m_srf(:, nsrf))
1044        END DO
1045    
1046        if (conv_emanuel) then
1047           CALL histwrite_phy("ptop", ema_pct)
1048           CALL histwrite_phy("dnwd0", - mp)
1049        end if
1050    
1051      if (ok_instan) call histsync(nid_ins)      if (ok_instan) call histsync(nid_ins)
1052    
1053      IF (lafin) then      IF (lafin) then
1054         call NF95_CLOSE(ncid_startphy)         call NF95_CLOSE(ncid_startphy)
1055         CALL phyredem(pctsrf, ftsol, ftsoil, fqsurf, qsol, &         CALL phyredem(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, &
1056              fsnow, falbe, fevap, rain_fall, snow_fall, solsw, sollw, dlw, &              rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, agesno, &
1057              radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &              zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, q_ancien, &
1058              t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, &              rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
             w01)  
1059      end IF      end IF
1060    
1061      firstcal = .FALSE.      firstcal = .FALSE.

Legend:
Removed from v.298  
changed lines
  Added in v.306

  ViewVC Help
Powered by ViewVC 1.1.21