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

Diff of /trunk/phylmd/physiq.f

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

revision 215 by guez, Tue Mar 28 12:46:28 2017 UTC revision 227 by guez, Thu Nov 2 15:47:03 2017 UTC
# Line 26  contains Line 26  contains
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
# Line 36  contains Line 36  contains
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_m, only: day_ref, annee_ref
39      USE fcttre, ONLY: foeew, qsatl, qsats      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
42      USE histsync_m, ONLY: histsync      USE histsync_m, ONLY: histsync
# 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 184  contains Line 184  contains
184      REAL cdragh(klon) ! drag coefficient pour T and Q      REAL cdragh(klon) ! drag coefficient pour T and Q
185      REAL cdragm(klon) ! drag coefficient pour vent      REAL cdragm(klon) ! drag coefficient pour vent
186    
     ! Pour phytrac :  
187      REAL ycoefh(klon, 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  
188    
189      REAL, save:: ffonte(klon, nbsrf)      REAL, save:: ffonte(klon, nbsrf)
190      ! flux thermique utilise pour fondre la neige      ! flux thermique utilise pour fondre la neige
# Line 219  contains Line 216  contains
216      real devap(klon) ! derivative of the evaporation flux at the surface      real devap(klon) ! derivative of the evaporation flux at the surface
217      REAL sens(klon) ! flux de chaleur sensible au sol      REAL sens(klon) ! flux de chaleur sensible au sol
218      real dsens(klon) ! derivee du flux de chaleur sensible au sol      real dsens(klon) ! derivee du flux de chaleur sensible au sol
219      REAL, save:: dlw(klon) ! derivee infra rouge      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, save:: fder(klon) ! Derive de flux (sensible et latente)      REAL fder(klon) ! Derive 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 234  contains Line 231  contains
231    
232      INTEGER julien      INTEGER julien
233      REAL, save:: pctsrf(klon, nbsrf) ! percentage of surface      REAL, save:: pctsrf(klon, nbsrf) ! percentage of surface
234      REAL, save:: albsol(klon) ! albedo du sol total visible      REAL, save:: albsol(klon) ! albedo du sol total, visible, moyen par maille
235      REAL, SAVE:: wo(klon, llm) ! column density of ozone in a cell, in kDU      REAL, SAVE:: wo(klon, llm) ! column density of ozone in a cell, in kDU
236      real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2      real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
237    
# Line 274  contains Line 271  contains
271      REAL cldl(klon), cldm(klon), cldh(klon) ! nuages bas, moyen et haut      REAL cldl(klon), cldm(klon), cldh(klon) ! nuages bas, moyen et haut
272      REAL cldt(klon), cldq(klon) ! nuage total, eau liquide integree      REAL cldt(klon), cldq(klon) ! nuage total, eau liquide integree
273    
274      REAL zxqsurf(klon), zxfluxlat(klon)      REAL zxfluxlat(klon)
   
275      REAL dist, mu0(klon), fract(klon)      REAL dist, mu0(klon), fract(klon)
276      real longi      real longi
277      REAL z_avant(klon), z_apres(klon), z_factor(klon)      REAL z_avant(klon), z_apres(klon), z_factor(klon)
# Line 339  contains Line 335  contains
335      real rain_lsc(klon)      real rain_lsc(klon)
336      REAL, save:: snow_con(klon) ! neige (mm / s)      REAL, save:: snow_con(klon) ! neige (mm / s)
337      real snow_lsc(klon)      real snow_lsc(klon)
338      REAL d_ts(klon, nbsrf)      REAL d_ts(klon, nbsrf) ! variation of ftsol
339    
340      REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)      REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)
341      REAL d_t_vdf(klon, llm), d_q_vdf(klon, llm)      REAL d_t_vdf(klon, llm), d_q_vdf(klon, llm)
# Line 382  contains Line 378  contains
378      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.
379    
380      real date0      real date0
381      REAL ztsol(klon)      REAL tsol(klon)
382    
383      REAL d_t_ec(klon, llm)      REAL d_t_ec(klon, llm)
384      ! tendance due \`a la conversion d'\'energie cin\'etique en      ! tendance due \`a la conversion d'\'energie cin\'etique en
# Line 391  contains Line 387  contains
387      REAL, save:: t2m(klon, nbsrf), q2m(klon, nbsrf)      REAL, save:: t2m(klon, nbsrf), q2m(klon, nbsrf)
388      ! temperature and humidity at 2 m      ! temperature and humidity at 2 m
389    
390      REAL, save:: u10m(klon, nbsrf), v10m(klon, nbsrf) ! vents a 10 m      REAL, save:: u10m_srf(klon, nbsrf), v10m_srf(klon, nbsrf)
391        ! composantes du vent \`a 10 m
392        
393      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
394      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
395    
396      ! Aerosol effects:      ! Aerosol effects:
397    
     REAL sulfate(klon, llm) ! SO4 aerosol concentration (micro g / m3)  
   
     REAL, save:: sulfate_pi(klon, llm)  
     ! SO4 aerosol concentration, in \mu g / m3, pre-industrial value  
   
     REAL cldtaupi(klon, llm)  
     ! cloud optical thickness for pre-industrial aerosols  
   
     REAL re(klon, llm) ! Cloud droplet effective radius  
     REAL fl(klon, llm) ! denominator of re  
   
     ! Aerosol optical properties  
     REAL, save:: tau_ae(klon, llm, 2), piz_ae(klon, llm, 2)  
     REAL, save:: cg_ae(klon, llm, 2)  
   
398      REAL, save:: topswad(klon), solswad(klon) ! aerosol direct effect      REAL, save:: topswad(klon), solswad(klon) ! aerosol direct effect
     REAL, save:: topswai(klon), solswai(klon) ! aerosol indirect effect  
   
399      LOGICAL:: ok_ade = .false. ! apply aerosol direct effect      LOGICAL:: ok_ade = .false. ! apply aerosol direct effect
     LOGICAL:: ok_aie = .false. ! apply aerosol indirect effect  
400    
401      REAL:: bl95_b0 = 2., bl95_b1 = 0.2      REAL:: bl95_b0 = 2., bl95_b1 = 0.2
402      ! Parameters in equation (D) of Boucher and Lohmann (1995, Tellus      ! Parameters in equation (D) of Boucher and Lohmann (1995, Tellus
# Line 429  contains Line 409  contains
409      integer, save:: ncid_startphy      integer, save:: ncid_startphy
410    
411      namelist /physiq_nml/ fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, &      namelist /physiq_nml/ fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, &
412           ratqsbas, ratqshaut, ok_ade, ok_aie, bl95_b0, bl95_b1, &           ratqsbas, ratqshaut, ok_ade, bl95_b0, bl95_b1, iflag_thermals, &
413           iflag_thermals, nsplit_thermals           nsplit_thermals
414    
415      !----------------------------------------------------------------      !----------------------------------------------------------------
416    
# Line 439  contains Line 419  contains
419    
420      test_firstcal: IF (firstcal) THEN      test_firstcal: IF (firstcal) THEN
421         ! initialiser         ! initialiser
422         u10m = 0.         u10m_srf = 0.
423         v10m = 0.         v10m_srf = 0.
424         t2m = 0.         t2m = 0.
425         q2m = 0.         q2m = 0.
426         ffonte = 0.         ffonte = 0.
427         fqcalving = 0.         fqcalving = 0.
        piz_ae = 0.  
        tau_ae = 0.  
        cg_ae = 0.  
428         rain_con = 0.         rain_con = 0.
429         snow_con = 0.         snow_con = 0.
        topswai = 0.  
        topswad = 0.  
        solswai = 0.  
        solswad = 0.  
   
430         d_u_con = 0.         d_u_con = 0.
431         d_v_con = 0.         d_v_con = 0.
432         rnebcon0 = 0.         rnebcon0 = 0.
433         clwcon0 = 0.         clwcon0 = 0.
434         rnebcon = 0.         rnebcon = 0.
435         clwcon = 0.         clwcon = 0.
   
436         pblh =0. ! Hauteur de couche limite         pblh =0. ! Hauteur de couche limite
437         plcl =0. ! Niveau de condensation de la CLA         plcl =0. ! Niveau de condensation de la CLA
438         capCL =0. ! CAPE de couche limite         capCL =0. ! CAPE de couche limite
# Line 513  contains Line 484  contains
484    
485         ! Initialisation des sorties         ! Initialisation des sorties
486    
487         call ini_histins(dtphys)         call ini_histins(dtphys, ok_newmicro)
488         CALL ymds2ju(annee_ref, 1, day_ref, 0., date0)         CALL ymds2ju(annee_ref, 1, day_ref, 0., date0)
489         ! Positionner date0 pour initialisation de ORCHIDEE         ! Positionner date0 pour initialisation de ORCHIDEE
490         print *, 'physiq date0: ', date0         print *, 'physiq date0: ', date0
# Line 529  contains Line 500  contains
500      ql_seri = qx(:, :, iliq)      ql_seri = qx(:, :, iliq)
501      tr_seri = qx(:, :, 3:nqmx)      tr_seri = qx(:, :, 3:nqmx)
502    
503      ztsol = sum(ftsol * pctsrf, dim = 2)      tsol = sum(ftsol * pctsrf, dim = 2)
504    
505      ! Diagnostic de la tendance dynamique :      ! Diagnostic de la tendance dynamique :
506      IF (ancien_ok) THEN      IF (ancien_ok) THEN
# Line 584  contains Line 555  contains
555    
556      CALL orbite(REAL(julien), longi, dist)      CALL orbite(REAL(julien), longi, dist)
557      CALL zenang(longi, time, dtphys * radpas, mu0, fract)      CALL zenang(longi, time, dtphys * radpas, mu0, fract)
   
     ! Calcul de l'abedo moyen par maille  
558      albsol = sum(falbe * pctsrf, dim = 2)      albsol = sum(falbe * pctsrf, dim = 2)
559    
560      ! R\'epartition sous maille des flux longwave et shortwave      ! R\'epartition sous maille des flux longwave et shortwave
561      ! R\'epartition du longwave par sous-surface lin\'earis\'ee      ! R\'epartition du longwave par sous-surface lin\'earis\'ee
562    
563      forall (nsrf = 1: nbsrf)      forall (nsrf = 1: nbsrf)
564         fsollw(:, nsrf) = sollw + 4. * RSIGMA * ztsol**3 &         fsollw(:, nsrf) = sollw + 4. * RSIGMA * tsol**3 &
565              * (ztsol - ftsol(:, nsrf))              * (tsol - ftsol(:, nsrf))
566         fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)         fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)
567      END forall      END forall
568    
     fder = dlw  
   
569      CALL clmain(dtphys, pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &      CALL clmain(dtphys, pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &
570           ftsol, cdmmax, cdhmax, ksta, ksta_ter, ok_kzmin, ftsoil, qsol, &           ftsol, cdmmax, cdhmax, ksta, ksta_ter, ok_kzmin, ftsoil, qsol, &
571           paprs, play, fsnow, fqsurf, fevap, falbe, fluxlat, rain_fall, &           paprs, play, fsnow, fqsurf, fevap, falbe, fluxlat, rain_fall, &
572           snow_fall, fsolsw, fsollw, fder, frugs, agesno, rugoro, d_t_vdf, &           snow_fall, fsolsw, fsollw, frugs, agesno, rugoro, d_t_vdf, d_q_vdf, &
573           d_q_vdf, d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, flux_u, flux_v, &           d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, flux_u, flux_v, cdragh, &
574           cdragh, cdragm, q2, dsens, devap, ycoefh, yu1, yv1, t2m, q2m, u10m, &           cdragm, q2, dsens, devap, ycoefh, t2m, q2m, u10m_srf, v10m_srf, &
575           v10m, pblh, capCL, oliqCL, cteiCL, pblT, therm, trmb1, trmb2, trmb3, &           pblh, capCL, oliqCL, cteiCL, pblT, therm, trmb1, trmb2, trmb3, plcl, &
576           plcl, fqcalving, ffonte, run_off_lic_0)           fqcalving, ffonte, run_off_lic_0)
577    
578      ! Incr\'ementation des flux      ! Incr\'ementation des flux
579    
# Line 627  contains Line 594  contains
594    
595      call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf')      call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf')
596      ftsol = ftsol + d_ts      ftsol = ftsol + d_ts
597      ztsol = sum(ftsol * pctsrf, dim = 2)      tsol = sum(ftsol * pctsrf, dim = 2)
598      zxfluxlat = sum(fluxlat * pctsrf, dim = 2)      zxfluxlat = sum(fluxlat * pctsrf, dim = 2)
599      zt2m = sum(t2m * pctsrf, dim = 2)      zt2m = sum(t2m * pctsrf, dim = 2)
600      zq2m = sum(q2m * pctsrf, dim = 2)      zq2m = sum(q2m * pctsrf, dim = 2)
601      zu10m = sum(u10m * pctsrf, dim = 2)      u10m = sum(u10m_srf * pctsrf, dim = 2)
602      zv10m = sum(v10m * pctsrf, dim = 2)      v10m = sum(v10m_srf * pctsrf, dim = 2)
603      zxffonte = sum(ffonte * pctsrf, dim = 2)      zxffonte = sum(ffonte * pctsrf, dim = 2)
604      zxfqcalving = sum(fqcalving * pctsrf, dim = 2)      zxfqcalving = sum(fqcalving * pctsrf, dim = 2)
605      s_pblh = sum(pblh * pctsrf, dim = 2)      s_pblh = sum(pblh * pctsrf, dim = 2)
# Line 650  contains Line 617  contains
617      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
618         DO i = 1, klon         DO i = 1, klon
619            IF (pctsrf(i, nsrf) < epsfra) then            IF (pctsrf(i, nsrf) < epsfra) then
620               ftsol(i, nsrf) = ztsol(i)               ftsol(i, nsrf) = tsol(i)
621               t2m(i, nsrf) = zt2m(i)               t2m(i, nsrf) = zt2m(i)
622               q2m(i, nsrf) = zq2m(i)               q2m(i, nsrf) = zq2m(i)
623               u10m(i, nsrf) = zu10m(i)               u10m_srf(i, nsrf) = u10m(i)
624               v10m(i, nsrf) = zv10m(i)               v10m_srf(i, nsrf) = v10m(i)
625               ffonte(i, nsrf) = zxffonte(i)               ffonte(i, nsrf) = zxffonte(i)
626               fqcalving(i, nsrf) = zxfqcalving(i)               fqcalving(i, nsrf) = zxfqcalving(i)
627               pblh(i, nsrf) = s_pblh(i)               pblh(i, nsrf) = s_pblh(i)
# Line 671  contains Line 638  contains
638         ENDDO         ENDDO
639      ENDDO      ENDDO
640    
641      ! Calculer la dérive du flux infrarouge      dlw = - 4. * RSIGMA * tsol**3
   
     DO i = 1, klon  
        dlw(i) = - 4. * RSIGMA * ztsol(i)**3  
     ENDDO  
642    
643      ! Appeler la convection      ! Appeler la convection
644    
# Line 897  contains Line 860  contains
860         ENDDO         ENDDO
861      ENDDO      ENDDO
862    
     ! Introduce the aerosol direct and first indirect radiative forcings:  
     tau_ae = 0.  
     piz_ae = 0.  
     cg_ae = 0.  
   
863      ! Param\`etres optiques des nuages et quelques param\`etres pour      ! Param\`etres optiques des nuages et quelques param\`etres pour
864      ! diagnostics :      ! diagnostics :
865      if (ok_newmicro) then      if (ok_newmicro) then
866         CALL newmicro(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, &         CALL newmicro(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, &
867              cldh, cldl, cldm, cldt, cldq, flwp, fiwp, flwc, fiwc, ok_aie, &              cldh, cldl, cldm, cldt, cldq, flwp, fiwp, flwc, fiwc)
             sulfate, sulfate_pi, bl95_b0, bl95_b1, cldtaupi, re, fl)  
868      else      else
869         CALL nuage(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, cldh, &         CALL nuage(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, cldh, &
870              cldl, cldm, cldt, cldq, ok_aie, sulfate, sulfate_pi, bl95_b0, &              cldl, cldm, cldt, cldq)
             bl95_b1, cldtaupi, re, fl)  
871      endif      endif
872    
873      IF (MOD(itap - 1, radpas) == 0) THEN      IF (MOD(itap - 1, radpas) == 0) THEN
        ! Prescrire l'ozone :  
874         wo = ozonecm(REAL(julien), paprs)         wo = ozonecm(REAL(julien), paprs)
   
        ! Appeler le rayonnement mais calculer tout d'abord l'albedo du sol.  
        ! Calcul de l'abedo moyen par maille  
875         albsol = sum(falbe * pctsrf, dim = 2)         albsol = sum(falbe * pctsrf, dim = 2)
876           CALL radlwsw(dist, mu0, fract, paprs, play, tsol, albsol, t_seri, &
        ! Rayonnement (compatible Arpege-IFS) :  
        CALL radlwsw(dist, mu0, fract, paprs, play, ztsol, albsol, t_seri, &  
877              q_seri, wo, cldfra, cldemi, cldtau, heat, heat0, cool, cool0, &              q_seri, wo, cldfra, cldemi, cldtau, heat, heat0, cool, cool0, &
878              radsol, albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, &              radsol, albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, &
879              toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, &              toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, &
880              swup0, swup, ok_ade, ok_aie, tau_ae, piz_ae, cg_ae, topswad, &              swup0, swup, ok_ade, topswad, solswad)
             solswad, cldtaupi, topswai, solswai)  
881      ENDIF      ENDIF
882    
883      ! Ajouter la tendance des rayonnements (tous les pas)      ! Ajouter la tendance des rayonnements (tous les pas)
# Line 939  contains Line 888  contains
888         ENDDO         ENDDO
889      ENDDO      ENDDO
890    
     ! Calculer l'hydrologie de la surface  
     zxqsurf = sum(fqsurf * pctsrf, dim = 2)  
   
891      ! 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)
892      DO i = 1, klon      DO i = 1, klon
893         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)         bils(i) = radsol(i) - sens(i) + zxfluxlat(i)
# Line 985  contains Line 931  contains
931            ENDIF            ENDIF
932         ENDDO         ENDDO
933    
934         CALL lift_noro(klon, llm, dtphys, paprs, play, rlat, zmea, zstd, zpic, &         CALL lift_noro(dtphys, paprs, play, zmea, zstd, zpic, itest, t_seri, &
935              itest, t_seri, u_seri, v_seri, zulow, zvlow, zustrli, zvstrli, &              u_seri, v_seri, zulow, zvlow, zustrli, zvstrli, d_t_lif, &
936              d_t_lif, d_u_lif, d_v_lif)              d_u_lif, d_v_lif)
937    
938         ! Ajout des tendances :         ! Ajout des tendances :
939         DO k = 1, llm         DO k = 1, llm
# Line 1014  contains Line 960  contains
960         ENDDO         ENDDO
961      ENDDO      ENDDO
962    
963      CALL aaam_bud(rg, romega, rlat, rlon, pphis, zustrdr, zustrli, zustrph, &      CALL aaam_bud(rg, romega, pphis, zustrdr, zustrli, zustrph, zvstrdr, &
964           zvstrdr, zvstrli, zvstrph, paprs, u, v, aam, torsfc)           zvstrli, zvstrph, paprs, u, v, aam, torsfc)
965    
966      ! Calcul des tendances traceurs      ! Calcul des tendances traceurs
967      call phytrac(julien, time, firstcal, lafin, dtphys, t, paprs, play, mfu, &      call phytrac(julien, time, firstcal, lafin, dtphys, t, paprs, play, mfu, &
968           mfd, pde_u, pen_d, ycoefh, fm_therm, entr_therm, yu1, yv1, ftsol, &           mfd, pde_u, pen_d, ycoefh, fm_therm, entr_therm, u(:, 1), v(:, 1), &
969           pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, tr_seri, &           ftsol, pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, dnwd, &
970           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, dtphys)  
971    
972      ! Calculer le transport de l'eau et de l'energie (diagnostique)      ! Calculer le transport de l'eau et de l'energie (diagnostique)
973      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 1091  contains Line 1033  contains
1033      CALL histwrite_phy("precip", rain_fall + snow_fall)      CALL histwrite_phy("precip", rain_fall + snow_fall)
1034      CALL histwrite_phy("plul", rain_lsc + snow_lsc)      CALL histwrite_phy("plul", rain_lsc + snow_lsc)
1035      CALL histwrite_phy("pluc", rain_con + snow_con)      CALL histwrite_phy("pluc", rain_con + snow_con)
1036      CALL histwrite_phy("tsol", ztsol)      CALL histwrite_phy("tsol", tsol)
1037      CALL histwrite_phy("t2m", zt2m)      CALL histwrite_phy("t2m", zt2m)
1038      CALL histwrite_phy("q2m", zq2m)      CALL histwrite_phy("q2m", zq2m)
1039      CALL histwrite_phy("u10m", zu10m)      CALL histwrite_phy("u10m", u10m)
1040      CALL histwrite_phy("v10m", zv10m)      CALL histwrite_phy("v10m", v10m)
1041      CALL histwrite_phy("snow", snow_fall)      CALL histwrite_phy("snow", snow_fall)
1042      CALL histwrite_phy("cdrm", cdragm)      CALL histwrite_phy("cdrm", cdragm)
1043      CALL histwrite_phy("cdrh", cdragh)      CALL histwrite_phy("cdrh", cdragh)
# Line 1122  contains Line 1064  contains
1064         CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))         CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))
1065         CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))         CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))
1066         CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))         CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))
1067           CALL histwrite_phy("u10m_"//clnsurf(nsrf), u10m_srf(:, nsrf))
1068           CALL histwrite_phy("v10m_"//clnsurf(nsrf), v10m_srf(:, nsrf))
1069      END DO      END DO
1070    
1071      CALL histwrite_phy("albs", albsol)      CALL histwrite_phy("albs", albsol)
# Line 1155  contains Line 1099  contains
1099      CALL histwrite_phy("dtsw0", heat0 / 86400.)      CALL histwrite_phy("dtsw0", heat0 / 86400.)
1100      CALL histwrite_phy("dtlw0", - cool0 / 86400.)      CALL histwrite_phy("dtlw0", - cool0 / 86400.)
1101      CALL histwrite_phy("msnow", sum(fsnow * pctsrf, dim = 2))      CALL histwrite_phy("msnow", sum(fsnow * pctsrf, dim = 2))
1102        call histwrite_phy("qsurf", sum(fqsurf * pctsrf, dim = 2))
1103    
1104      if (ok_instan) call histsync(nid_ins)      if (ok_instan) call histsync(nid_ins)
1105    

Legend:
Removed from v.215  
changed lines
  Added in v.227

  ViewVC Help
Powered by ViewVC 1.1.21