/[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/phylmd/physiq.f revision 324 by guez, Wed Feb 6 15:58:03 2019 UTC trunk/phylmd/physiq.f90 revision 328 by guez, Thu Jun 13 14:40:06 2019 UTC
# Line 41  contains Line 41  contains
41      USE hgardfou_m, ONLY: hgardfou      USE hgardfou_m, ONLY: hgardfou
42      USE histsync_m, ONLY: histsync      USE histsync_m, ONLY: histsync
43      USE histwrite_phy_m, ONLY: histwrite_phy      USE histwrite_phy_m, ONLY: histwrite_phy
44      USE indicesol, ONLY: clnsurf, epsfra, is_lic, is_oce, is_sic, is_ter, &      USE indicesol, ONLY: clnsurf, epsfra, nbsrf
          nbsrf  
45      USE ini_histins_m, ONLY: ini_histins, nid_ins      USE ini_histins_m, ONLY: ini_histins, nid_ins
46      use lift_noro_m, only: lift_noro      use lift_noro_m, only: lift_noro
47      use netcdf95, only: NF95_CLOSE      use netcdf95, only: NF95_CLOSE
# Line 219  contains Line 218  contains
218      real dflux_t(klon) ! derivee du flux de chaleur sensible au sol      real dflux_t(klon) ! derivee du flux de chaleur sensible au sol
219      REAL, save:: dlw(klon) ! derivative of infra-red flux      REAL, save:: dlw(klon) ! derivative of infra-red flux
220      REAL bils(klon) ! bilan de chaleur au sol      REAL bils(klon) ! bilan de chaleur au sol
221      REAL fder(klon) ! Derive de flux (sensible et latente)      REAL fder(klon) ! d\'erive de flux (sensible et latente)
222      REAL ve(klon) ! integr. verticale du transport meri. de l'energie      REAL ve(klon) ! integr. verticale du transport meri. de l'energie
223      REAL vq(klon) ! integr. verticale du transport meri. de l'eau      REAL vq(klon) ! integr. verticale du transport meri. de l'eau
224      REAL ue(klon) ! integr. verticale du transport zonal de l'energie      REAL ue(klon) ! integr. verticale du transport zonal de l'energie
# Line 265  contains Line 264  contains
264      REAL, save:: topsw(klon), toplw(klon), solsw(klon)      REAL, save:: topsw(klon), toplw(klon), solsw(klon)
265    
266      REAL, save:: sollw(klon) ! surface net downward longwave flux, in W m-2      REAL, save:: sollw(klon) ! surface net downward longwave flux, in W m-2
267      real, save:: sollwdown(klon) ! downward LW flux at surface      real, save:: sollwdown(klon) ! downwelling longwave flux at surface
268      REAL, save:: topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)      REAL, save:: topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)
269      REAL, save:: albpla(klon)      REAL, save:: albpla(klon)
270    
# Line 335  contains Line 334  contains
334      real rain_lsc(klon)      real rain_lsc(klon)
335      REAL snow_con(klon) ! neige (mm / s)      REAL snow_con(klon) ! neige (mm / s)
336      real snow_lsc(klon)      real snow_lsc(klon)
     REAL d_ts(klon, nbsrf) ! variation of ftsol  
337    
338      REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)      REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)
339      REAL d_t_vdf(klon, llm), d_q_vdf(klon, llm)      REAL d_t_vdf(klon, llm), d_q_vdf(klon, llm)
# Line 544  contains Line 542  contains
542      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, &
543           ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, &           ftsol, cdmmax, cdhmax, ftsoil, qsol, paprs, play, fsnow, fqsurf, &
544           falbe, fluxlat, rain_fall, snow_fall, frugs, agesno, rugoro, d_t_vdf, &           falbe, fluxlat, rain_fall, snow_fall, frugs, agesno, rugoro, d_t_vdf, &
545           d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, flux_u, flux_v, &           d_q_vdf, d_u_vdf, d_v_vdf, flux_t, flux_q, flux_u, flux_v, cdragh, &
546           cdragh, cdragm, q2, dflux_t, dflux_q, coefh, t2m, q2m, u10m_srf, &           cdragm, q2, dflux_t, dflux_q, coefh, t2m, q2m, u10m_srf, v10m_srf, &
547           v10m_srf, pblh, capCL, oliqCL, cteiCL, pblT, therm, plcl, fqcalving, &           pblh, capCL, oliqCL, cteiCL, pblT, therm, plcl, fqcalving, ffonte, &
548           ffonte, run_off_lic_0, albsol, sollw, solsw, tsol)           run_off_lic_0, albsol, sollw, solsw, tsol)
549    
550      ! Incr\'ementation des flux      ! Incr\'ementation des flux
551    
# Line 565  contains Line 563  contains
563      ENDDO      ENDDO
564    
565      call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf')      call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf')
     ftsol = ftsol + d_ts ! update surface temperature  
566      tsol = sum(ftsol * pctsrf, dim = 2)      tsol = sum(ftsol * pctsrf, dim = 2)
567      zxfluxlat = sum(fluxlat * pctsrf, dim = 2)      zxfluxlat = sum(fluxlat * pctsrf, dim = 2)
568      zt2m = sum(t2m * pctsrf, dim = 2)      zt2m = sum(t2m * pctsrf, dim = 2)
# Line 655  contains Line 652  contains
652         z_factor = (z_avant - (rain_con + snow_con) * dtphys) / z_apres         z_factor = (z_avant - (rain_con + snow_con) * dtphys) / z_apres
653         DO k = 1, llm         DO k = 1, llm
654            DO i = 1, klon            DO i = 1, klon
655               IF (z_factor(i) > 1. + 1E-8 .OR. z_factor(i) < 1. - 1E-8) THEN               IF (z_factor(i) /= 1.) THEN
656                  q_seri(i, k) = q_seri(i, k) * z_factor(i)                  q_seri(i, k) = q_seri(i, k) * z_factor(i)
657               ENDIF               ENDIF
658            ENDDO            ENDDO
# Line 990  contains Line 987  contains
987      CALL histwrite_phy("bils", bils)      CALL histwrite_phy("bils", bils)
988      CALL histwrite_phy("sens", sens)      CALL histwrite_phy("sens", sens)
989      CALL histwrite_phy("fder", fder)      CALL histwrite_phy("fder", fder)
     CALL histwrite_phy("dtsvdfo", d_ts(:, is_oce))  
     CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))  
     CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))  
     CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))  
990      CALL histwrite_phy("zxfqcalving", sum(fqcalving * pctsrf, dim = 2))      CALL histwrite_phy("zxfqcalving", sum(fqcalving * pctsrf, dim = 2))
991      CALL histwrite_phy("albs", albsol)      CALL histwrite_phy("albs", albsol)
992      CALL histwrite_phy("tro3", wo * dobson_u * 1e3 / zmasse / rmo3 * md)      CALL histwrite_phy("tro3", wo * dobson_u * 1e3 / zmasse / rmo3 * md)
# Line 1016  contains Line 1009  contains
1009      CALL histwrite_phy("d_t_ec", d_t_ec)      CALL histwrite_phy("d_t_ec", d_t_ec)
1010      CALL histwrite_phy("dtsw0", heat0 / 86400.)      CALL histwrite_phy("dtsw0", heat0 / 86400.)
1011      CALL histwrite_phy("dtlw0", - cool0 / 86400.)      CALL histwrite_phy("dtlw0", - cool0 / 86400.)
1012        call histwrite_phy("pmflxr", pmflxr(:, :llm))
1013      CALL histwrite_phy("msnow", sum(fsnow * pctsrf, dim = 2))      CALL histwrite_phy("msnow", sum(fsnow * pctsrf, dim = 2))
1014      call histwrite_phy("qsurf", sum(fqsurf * pctsrf, dim = 2))      call histwrite_phy("qsurf", sum(fqsurf * pctsrf, dim = 2))
1015      call histwrite_phy("flat", zxfluxlat)      call histwrite_phy("flat", zxfluxlat)

Legend:
Removed from v.324  
changed lines
  Added in v.328

  ViewVC Help
Powered by ViewVC 1.1.21