/[lmdze]/trunk/Sources/phylmd/phytrac.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/phytrac.f

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

revision 18 by guez, Thu Aug 7 12:29:13 2008 UTC revision 38 by guez, Thu Jan 6 17:52:19 2011 UTC
# Line 1  Line 1 
1  module phytrac_m  module phytrac_m
2    
   ! This module is clean: no C preprocessor directive, no include line.  
   
3    IMPLICIT none    IMPLICIT none
4    
5    private    private
# Line 10  module phytrac_m Line 8  module phytrac_m
8  contains  contains
9    
10    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &
11         nq_phys, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &         nq_phys, pdtphys, u, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &
12         pde_u, pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, &         pde_u, pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, &
13         pctsrf, frac_impa, frac_nucl, presnivs, pphis, &         pctsrf, frac_impa, frac_nucl, pphis, pphi, albsol, rh, cldfra, rneb, &
14         pphi, albsol, rh, cldfra, rneb, diafra, cldliq, itop_con, &         diafra, cldliq, pmflxr, pmflxs, prfl, psfl, da, &
15         ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, &         phi, mp, upwd, dnwd, tr_seri, zmasse)
        tr_seri, zmasse)  
16    
17      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30
18    
# Line 23  contains Line 20  contains
20      ! Foujols, Olivia      ! Foujols, Olivia
21      ! Objet : moniteur général des tendances des traceurs      ! Objet : moniteur général des tendances des traceurs
22    
23      ! Remarques :      ! L'appel de "phytrac" se fait avec "nqmx-2" donc nous avons bien
     ! 1/ L'appel de "phytrac" se fait avec "nq-2" donc nous avons bien  
24      ! les vrais traceurs (en nombre "nbtr", sans la vapeur d'eau ni l'eau      ! les vrais traceurs (en nombre "nbtr", sans la vapeur d'eau ni l'eau
25      ! liquide) dans "phytrac".      ! liquide) dans "phytrac".
     ! 2/ Le choix du radon et du plomb se fait juste avec un "data"  
     ! (peu propre).  
     ! Pourrait-on avoir une variable qui indiquerait le type de traceur ?  
26    
27      use dimens_m, only: llm      use dimens_m, only: llm
28      use indicesol, only: nbsrf      use indicesol, only: nbsrf
# Line 37  contains Line 30  contains
30      use clesphys, only: ecrit_tra      use clesphys, only: ecrit_tra
31      use clesphys2, only: iflag_con      use clesphys2, only: iflag_con
32      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
33      use YOMCST, only: rg      use SUPHEC_M, only: rg
34      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
35      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
36      use phyetat0_m, only: rlat      use phyetat0_m, only: rlat
37      use o3_chem_m, only: o3_chem      use o3_chem_m, only: o3_chem
38      use ini_hist, only: ini_histrac      use ini_histrac_m, only: ini_histrac
39      use radiornpb_m, only: radiornpb      use radiornpb_m, only: radiornpb
40      use minmaxqfi_m, only: minmaxqfi      use minmaxqfi_m, only: minmaxqfi
41      use numer_rec, only: assert      use nr_util, only: assert
42      use press_coefoz_m, only: press_coefoz      use press_coefoz_m, only: press_coefoz
43    
     ! Arguments:  
   
     !   EN ENTREE:  
   
     !   divers:  
   
44      logical, intent(in):: rnpb      logical, intent(in):: rnpb
45    
46      integer, intent(in):: nq_phys      integer, intent(in):: nq_phys
# Line 62  contains Line 49  contains
49      integer, intent(in):: itap  ! number of calls to "physiq"      integer, intent(in):: itap  ! number of calls to "physiq"
50      integer, intent(in):: lmt_pas ! number of time steps of "physics" per day      integer, intent(in):: lmt_pas ! number of time steps of "physics" per day
51      integer, intent(in):: julien !jour julien, 1 <= julien <= 360      integer, intent(in):: julien !jour julien, 1 <= julien <= 360
     integer itop_con(klon)  
     integer ibas_con(klon)  
52      real, intent(in):: gmtime ! heure de la journée en fraction de jour      real, intent(in):: gmtime ! heure de la journée en fraction de jour
53      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)
54      real, intent(in):: t_seri(klon, llm) ! temperature, in K      real, intent(in):: t_seri(klon, llm) ! temperature, in K
# Line 72  contains Line 57  contains
57      ! (mass fractions of tracers, excluding water, at mid-layers)      ! (mass fractions of tracers, excluding water, at mid-layers)
58    
59      real u(klon, llm)      real u(klon, llm)
     real v(klon, llm)  
60      real rh(klon, llm)     ! humidite relative      real rh(klon, llm)     ! humidite relative
61      real cldliq(klon, llm) ! eau liquide nuageuse      real cldliq(klon, llm) ! eau liquide nuageuse
62      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)      real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)
# Line 91  contains Line 75  contains
75    
76      real pphi(klon, llm) ! geopotentiel      real pphi(klon, llm) ! geopotentiel
77      real pphis(klon)      real pphis(klon)
     REAL, intent(in):: presnivs(llm)  
78      logical, intent(in):: firstcal ! first call to "calfis"      logical, intent(in):: firstcal ! first call to "calfis"
79      logical, intent(in):: lafin ! fin de la physique      logical, intent(in):: lafin ! fin de la physique
80    
# Line 221  contains Line 204  contains
204         inirnpb=rnpb         inirnpb=rnpb
205    
206         ! Initialisation des sorties :         ! Initialisation des sorties :
207         call ini_histrac(nid_tra, pdtphys, presnivs, nq_phys, lessivage)         call ini_histrac(nid_tra, pdtphys, nq_phys, lessivage)
208    
209         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
210         ! Initialisation du traceur dans le sol (couche limite radonique)         ! Initialisation du traceur dans le sol (couche limite radonique)
# Line 470  contains Line 453  contains
453        ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30        ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30
454    
455        use dimens_m, only: iim, jjm, llm        use dimens_m, only: iim, jjm, llm
456        use ioipsl, only: histwrite, histsync        use histcom, only: histsync
457          use histwrite_m, only: histwrite
458        use temps, only: itau_phy        use temps, only: itau_phy
459        use iniadvtrac_m, only: tnom        use iniadvtrac_m, only: tnom
460        use comgeomphy, only: airephy        use comgeomphy, only: airephy
461        use dimphy, only: klon        use dimphy, only: klon
462          use grid_change, only: gr_phy_write_2d
463          use gr_phy_write_3d_m, only: gr_phy_write_3d
464    
465        logical, intent(in):: lessivage        logical, intent(in):: lessivage
466    
# Line 487  contains Line 473  contains
473        ! Variables local to the procedure:        ! Variables local to the procedure:
474        integer it        integer it
475        integer itau_w   ! pas de temps ecriture        integer itau_w   ! pas de temps ecriture
       REAL zx_tmp_2d(iim, jjm+1), zx_tmp_3d(iim, jjm+1, llm)  
476        logical, parameter:: ok_sync = .true.        logical, parameter:: ok_sync = .true.
477    
478        !-----------------------------------------------------        !-----------------------------------------------------
479    
480        itau_w = itau_phy + itap        itau_w = itau_phy + itap
481    
482        CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d)        CALL histwrite(nid_tra, "phis", itau_w, gr_phy_write_2d(pphis))
483        CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d)        CALL histwrite(nid_tra, "aire", itau_w, gr_phy_write_2d(airephy))
484          CALL histwrite(nid_tra, "zmasse", itau_w, gr_phy_write_3d(zmasse))
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d)        
       CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d)  
   
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, zmasse, zx_tmp_3d)        
       CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d)  
485    
486        DO it=1, nq_phys        DO it=1, nq_phys
487           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, tr_seri(1, 1, it), zx_tmp_3d)           CALL histwrite(nid_tra, tnom(it+2), itau_w, &
488           CALL histwrite(nid_tra, tnom(it+2), itau_w, zx_tmp_3d)                gr_phy_write_3d(tr_seri(:, :, it)))
489           if (lessivage) THEN           if (lessivage) THEN
490              CALL gr_fi_ecrit(llm, klon, iim, jjm+1, flestottr(1, 1, it), &              CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, &
491                   zx_tmp_3d)                   gr_phy_write_3d(flestottr(:, :, it)))
             CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d)  
492           endif           endif
493             CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, &
494           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_th(1, 1, it), zx_tmp_3d)                gr_phy_write_3d(d_tr_th(:, :, it)))
495           CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, zx_tmp_3d)           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, &
496           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cv(1, 1, it), zx_tmp_3d)                gr_phy_write_3d(d_tr_cv(:, :, it)))
497           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d)           CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, &
498           CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cl(1, 1, it), zx_tmp_3d)                gr_phy_write_3d(d_tr_cl(:, :, it)))
          CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, zx_tmp_3d)  
499        ENDDO        ENDDO
500    
501        CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d)        CALL histwrite(nid_tra, "pplay", itau_w, gr_phy_write_3d(pplay))
502        CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d)        CALL histwrite(nid_tra, "T", itau_w, gr_phy_write_3d(t_seri))
   
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, t_seri, zx_tmp_3d)  
       CALL histwrite(nid_tra, "t", itau_w, zx_tmp_3d)  
503    
504        if (ok_sync) then        if (ok_sync) then
505           call histsync(nid_tra)           call histsync(nid_tra)

Legend:
Removed from v.18  
changed lines
  Added in v.38

  ViewVC Help
Powered by ViewVC 1.1.21