/[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 307 by guez, Tue Sep 11 12:52:28 2018 UTC revision 324 by guez, Wed Feb 6 15:58:03 2019 UTC
# Line 29  contains Line 29  contains
29      USE conf_gcm_m, ONLY: 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_m, ONLY: iflag_thermals, ctherm
33      use diagcld2_m, only: diagcld2      use diagcld2_m, only: diagcld2
34      USE dimensions, 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_chosen_m, only: day_ref, annee_ref
39      USE fcttre, ONLY: foeew      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
# Line 144  contains Line 144  contains
144      ! Radiative transfer computations are made every "radpas" call to      ! Radiative transfer computations are made every "radpas" call to
145      ! "physiq".      ! "physiq".
146    
147      REAL, save:: radsol(klon) ! bilan radiatif au sol calcule par code radiatif      REAL, save:: radsol(klon)
148      REAL, save:: ftsol(klon, nbsrf) ! skin temperature of surface fraction      ! Bilan radiatif net au sol (W/m2), positif vers le bas. Must be
149        ! saved because radlwsw is not called at every time step.
150        
151        REAL, save:: ftsol(klon, nbsrf) ! skin temperature of surface fraction, in K
152    
153      REAL, save:: ftsoil(klon, nsoilmx, nbsrf)      REAL, save:: ftsoil(klon, nsoilmx, nbsrf)
154      ! soil temperature of surface fraction      ! soil temperature of surface fraction
155    
156      REAL fluxlat(klon, nbsrf)      REAL fluxlat(klon, nbsrf) ! flux de chaleur latente, en W m-2
157    
158      REAL, save:: fqsurf(klon, nbsrf)      REAL, save:: fqsurf(klon, nbsrf)
159      ! humidite de l'air au contact de la surface      ! humidite de l'air au contact de la surface
# Line 245  contains Line 248  contains
248      REAL cldemi(klon, llm) ! emissivite infrarouge      REAL cldemi(klon, llm) ! emissivite infrarouge
249    
250      REAL flux_q(klon, nbsrf) ! flux turbulent d'humidite à la surface      REAL flux_q(klon, nbsrf) ! flux turbulent d'humidite à la surface
251      REAL flux_t(klon, nbsrf) ! flux turbulent de chaleur à la surface  
252        REAL flux_t(klon, nbsrf)
253        ! flux de chaleur sensible (c_p T) (W / m2) (orientation positive
254        ! vers le bas) à la surface
255    
256      REAL flux_u(klon, nbsrf), flux_v(klon, nbsrf)      REAL flux_u(klon, nbsrf), flux_v(klon, nbsrf)
257      ! tension du vent (flux turbulent de vent) à la surface, en Pa      ! tension du vent (flux turbulent de vent) à la surface, en Pa
# Line 257  contains Line 263  contains
263      REAL, save:: cool(klon, llm) ! refroidissement infrarouge      REAL, save:: cool(klon, llm) ! refroidissement infrarouge
264      REAL, save:: cool0(klon, llm) ! refroidissement infrarouge ciel clair      REAL, save:: cool0(klon, llm) ! refroidissement infrarouge ciel clair
265      REAL, save:: topsw(klon), toplw(klon), solsw(klon)      REAL, save:: topsw(klon), toplw(klon), solsw(klon)
266      REAL, save:: sollw(klon) ! rayonnement infrarouge montant \`a la surface  
267        REAL, save:: sollw(klon) ! surface net downward longwave flux, in W m-2
268      real, save:: sollwdown(klon) ! downward LW flux at surface      real, save:: sollwdown(klon) ! downward LW flux at surface
269      REAL, save:: topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)      REAL, save:: topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)
270      REAL, save:: albpla(klon)      REAL, save:: albpla(klon)
# Line 273  contains Line 280  contains
280      real longi      real longi
281      REAL z_avant(klon), z_apres(klon), z_factor(klon)      REAL z_avant(klon), z_apres(klon), z_factor(klon)
282      REAL zb      REAL zb
283      REAL zx_t, zx_qs, zcor      REAL zx_qs, zcor
284      real zqsat(klon, llm)      real zqsat(klon, llm)
285      INTEGER i, k, iq, nsrf      INTEGER i, k, iq, nsrf
286      REAL zphi(klon, llm)      REAL zphi(klon, llm)
# Line 400  contains Line 407  contains
407      integer, save:: ncid_startphy      integer, save:: ncid_startphy
408    
409      namelist /physiq_nml/ fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, &      namelist /physiq_nml/ fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, &
410           ratqsbas, ratqshaut, ok_ade, bl95_b0, bl95_b1, iflag_thermals, &           ratqsbas, ratqshaut, ok_ade, bl95_b0, bl95_b1
          nsplit_thermals  
411    
412      !----------------------------------------------------------------      !----------------------------------------------------------------
413    
# Line 429  contains Line 435  contains
435         pblt =0.         pblt =0.
436         therm =0.         therm =0.
437    
        iflag_thermals = 0  
        nsplit_thermals = 1  
438         print *, "Enter namelist 'physiq_nml'."         print *, "Enter namelist 'physiq_nml'."
439         read(unit=*, nml=physiq_nml)         read(unit=*, nml=physiq_nml)
440         write(unit_nml, nml=physiq_nml)         write(unit_nml, nml=physiq_nml)
441    
442           call ctherm
443         call conf_phys         call conf_phys
444    
445         ! Initialiser les compteurs:         ! Initialiser les compteurs:
# Line 546  contains Line 551  contains
551    
552      ! Incr\'ementation des flux      ! Incr\'ementation des flux
553    
554      sens = - sum(flux_t * pctsrf, dim = 2)      sens = sum(flux_t * pctsrf, dim = 2)
555      evap = - sum(flux_q * pctsrf, dim = 2)      evap = - sum(flux_q * pctsrf, dim = 2)
556      fder = dlw + dflux_t + dflux_q      fder = dlw + dflux_t + dflux_q
557    
# Line 666  contains Line 671  contains
671      fm_therm = 0.      fm_therm = 0.
672      entr_therm = 0.      entr_therm = 0.
673    
674      if (iflag_thermals == 0) then      if (iflag_thermals) then
675         ! Ajustement sec         call calltherm(play, paprs, pphi, u_seri, v_seri, t_seri, q_seri, &
676                d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm)
677        else
678         CALL ajsec(paprs, play, t_seri, q_seri, d_t_ajs, d_q_ajs)         CALL ajsec(paprs, play, t_seri, q_seri, d_t_ajs, d_q_ajs)
679         t_seri = t_seri + d_t_ajs         t_seri = t_seri + d_t_ajs
680         q_seri = q_seri + d_q_ajs         q_seri = q_seri + d_q_ajs
     else  
        call calltherm(play, paprs, pphi, u_seri, v_seri, t_seri, q_seri, &  
             d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm)  
681      endif      endif
682    
683      ! Caclul des ratqs      ! Caclul des ratqs
# Line 806  contains Line 810  contains
810      ! Humidit\'e relative pour diagnostic :      ! Humidit\'e relative pour diagnostic :
811      DO k = 1, llm      DO k = 1, llm
812         DO i = 1, klon         DO i = 1, klon
813            zx_t = t_seri(i, k)            zx_qs = r2es * FOEEW(t_seri(i, k), rtt >= t_seri(i, k)) / play(i, k)
           zx_qs = r2es * FOEEW(zx_t, rtt >= zx_t) / play(i, k)  
814            zx_qs = MIN(0.5, zx_qs)            zx_qs = MIN(0.5, zx_qs)
815            zcor = 1. / (1. - retv * zx_qs)            zcor = 1. / (1. - retv * zx_qs)
816            zx_qs = zx_qs * zcor            zx_qs = zx_qs * zcor
# Line 846  contains Line 849  contains
849    
850      ! 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)
851      DO i = 1, klon      DO i = 1, klon
852         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)         bils(i) = radsol(i) + sens(i) + zxfluxlat(i)
853      ENDDO      ENDDO
854    
855      ! Param\'etrisation de l'orographie \`a l'\'echelle sous-maille :      ! Param\'etrisation de l'orographie \`a l'\'echelle sous-maille :
# Line 912  contains Line 915  contains
915    
916      ! diag. bilKP      ! diag. bilKP
917    
918      CALL transp_lay(paprs, t_seri, q_seri, u_seri, v_seri, zphi, &      CALL transp_lay(paprs, t_seri, q_seri, u_seri, v_seri, zphi, ve_lay, &
919           ve_lay, vq_lay, ue_lay, uq_lay)           vq_lay, ue_lay, uq_lay)
920    
921      ! Accumuler les variables a stocker dans les fichiers histoire:      ! Accumuler les variables a stocker dans les fichiers histoire:
922    
# Line 982  contains Line 985  contains
985      CALL histwrite_phy("topl", toplw)      CALL histwrite_phy("topl", toplw)
986      CALL histwrite_phy("evap", evap)      CALL histwrite_phy("evap", evap)
987      CALL histwrite_phy("sols", solsw)      CALL histwrite_phy("sols", solsw)
988      CALL histwrite_phy("soll", sollw)      CALL histwrite_phy("rls", sollw)
989      CALL histwrite_phy("solldown", sollwdown)      CALL histwrite_phy("solldown", sollwdown)
990      CALL histwrite_phy("bils", bils)      CALL histwrite_phy("bils", bils)
991      CALL histwrite_phy("sens", - sens)      CALL histwrite_phy("sens", sens)
992      CALL histwrite_phy("fder", fder)      CALL histwrite_phy("fder", fder)
993      CALL histwrite_phy("dtsvdfo", d_ts(:, is_oce))      CALL histwrite_phy("dtsvdfo", d_ts(:, is_oce))
994      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))      CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))
# Line 1018  contains Line 1021  contains
1021      call histwrite_phy("flat", zxfluxlat)      call histwrite_phy("flat", zxfluxlat)
1022    
1023      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
        CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)  
1024         CALL histwrite_phy("fract_"//clnsurf(nsrf), pctsrf(:, nsrf))         CALL histwrite_phy("fract_"//clnsurf(nsrf), pctsrf(:, nsrf))
1025         CALL histwrite_phy("sens_"//clnsurf(nsrf), flux_t(:, nsrf))         CALL histwrite_phy("sens_"//clnsurf(nsrf), flux_t(:, nsrf))
1026         CALL histwrite_phy("lat_"//clnsurf(nsrf), fluxlat(:, nsrf))         CALL histwrite_phy("lat_"//clnsurf(nsrf), fluxlat(:, nsrf))

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

  ViewVC Help
Powered by ViewVC 1.1.21