/[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 159 by guez, Tue Jul 21 15:29:52 2015 UTC revision 191 by guez, Mon May 9 19:56:28 2016 UTC
# Line 7  module phytrac_m Line 7  module phytrac_m
7    
8  contains  contains
9    
10    SUBROUTINE phytrac(itap, lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, &    SUBROUTINE phytrac(lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, &
11         t_seri, paprs, pplay, pmfu, pmfd, pde_u, pen_d, coefh, fm_therm, &         t_seri, paprs, pplay, pmfu, pmfd, pde_u, pen_d, coefh, fm_therm, &
12         entr_therm, yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, da, phi, &         entr_therm, yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, da, phi, &
13         mp, upwd, dnwd, tr_seri, zmasse, ncid_startphy, nid_ins)         mp, upwd, dnwd, tr_seri, zmasse, ncid_startphy)
14    
15      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30 (SVN revision 679)      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30 (SVN revision 679)
16    
# Line 28  contains Line 28  contains
28    
29      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
30      use clesphys, only: ecrit_tra      use clesphys, only: ecrit_tra
31      use clesphys2, only: iflag_con      use clesphys2, only: conv_emanuel
32      use cltrac_m, only: cltrac      use cltrac_m, only: cltrac
33      use cltracrn_m, only: cltracrn      use cltracrn_m, only: cltracrn
34      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
# Line 38  contains Line 38  contains
38      use indicesol, only: nbsrf      use indicesol, only: nbsrf
39      use initrrnpb_m, only: initrrnpb      use initrrnpb_m, only: initrrnpb
40      use minmaxqfi_m, only: minmaxqfi      use minmaxqfi_m, only: minmaxqfi
41        use netcdf, only: NF90_FILL_float
42      use netcdf95, only: nf95_inq_varid, nf95_get_var, nf95_put_var      use netcdf95, only: nf95_inq_varid, nf95_get_var, nf95_put_var
43      use nflxtr_m, only: nflxtr      use nflxtr_m, only: nflxtr
44      use nr_util, only: assert      use nr_util, only: assert
# Line 48  contains Line 49  contains
49      use radiornpb_m, only: radiornpb      use radiornpb_m, only: radiornpb
50      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
51      use SUPHEC_M, only: rg      use SUPHEC_M, only: rg
52        use time_phylmdz, only: itap
53    
     integer, intent(in):: itap ! number of calls to "physiq"  
54      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
55      integer, intent(in):: julien !jour julien, 1 <= julien <= 360      integer, intent(in):: julien !jour julien, 1 <= julien <= 360
56      real, intent(in):: gmtime ! heure de la journ\'ee en fraction de jour      real, intent(in):: gmtime ! heure de la journ\'ee en fraction de jour
# Line 101  contains Line 102  contains
102      real, intent(in):: zmasse(:, :) ! (klon, llm)      real, intent(in):: zmasse(:, :) ! (klon, llm)
103      ! (column-density of mass of air in a cell, in kg m-2)      ! (column-density of mass of air in a cell, in kg m-2)
104    
105      integer, intent(in):: ncid_startphy, nid_ins      integer, intent(in):: ncid_startphy
106    
107      ! Local:      ! Local:
108    
# Line 194  contains Line 195  contains
195    
196         call nf95_inq_varid(ncid_startphy, "trs", varid)         call nf95_inq_varid(ncid_startphy, "trs", varid)
197         call nf95_get_var(ncid_startphy, varid, trs(:, 1))         call nf95_get_var(ncid_startphy, varid, trs(:, 1))
198           if (any(trs(:, 1) == NF90_FILL_float)) call abort_gcm("phytrac", &
199                "some missing values in trs(:, 1)")
200    
201         ! Initialisation de la fraction d'aerosols lessivee         ! Initialisation de la fraction d'aerosols lessivee
202    
# Line 227  contains Line 230  contains
230      if (convection) then      if (convection) then
231         ! Calcul de l'effet de la convection         ! Calcul de l'effet de la convection
232         DO it=1, nqmx - 2         DO it=1, nqmx - 2
233            if (iflag_con == 2) then            if (conv_emanuel) then
              ! Tiedke  
              CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, &  
                   tr_seri(:, :, it), d_tr_cv(:, :, it))  
           else if (iflag_con == 3) then  
              ! Emanuel  
234               call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, &               call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, &
235                    dnwd, d_tr_cv(:, :, it))                    dnwd, d_tr_cv(:, :, it))
236              else
237                 CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, &
238                      tr_seri(:, :, it), d_tr_cv(:, :, it))
239            endif            endif
240    
241            DO k = 1, llm            DO k = 1, llm
# Line 339  contains Line 340  contains
340         ! Ozone as a tracer:         ! Ozone as a tracer:
341         if (mod(itap - 1, lmt_pas) == 0) then         if (mod(itap - 1, lmt_pas) == 0) then
342            ! Once per day, update the coefficients for ozone chemistry:            ! Once per day, update the coefficients for ozone chemistry:
343            call regr_pr_comb_coefoz(julien)            call regr_pr_comb_coefoz(julien, paprs, pplay)
344         end if         end if
345         call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))         call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))
346      end if      end if
# Line 394  contains Line 395  contains
395      ENDIF      ENDIF
396    
397      ! Ecriture des sorties      ! Ecriture des sorties
398      call write_histrac(lessivage, itap, nid_ins)      call write_histrac(lessivage)
399    
400      if (lafin) then      if (lafin) then
401         call nf95_inq_varid(ncid_restartphy, "trs", varid)         call nf95_inq_varid(ncid_restartphy, "trs", varid)
# Line 403  contains Line 404  contains
404    
405    contains    contains
406    
407      subroutine write_histrac(lessivage, itap, nid_ins)      subroutine write_histrac(lessivage)
408    
409        ! 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
410    
411        use dimens_m, only: iim, jjm, llm        use gr_phy_write_m, only: gr_phy_write
       use histsync_m, only: histsync  
412        use histwrite_m, only: histwrite        use histwrite_m, only: histwrite
       use temps, only: itau_phy  
413        use iniadvtrac_m, only: tname        use iniadvtrac_m, only: tname
414        use dimphy, only: klon        use ini_histins_m, only: nid_ins
415        use grid_change, only: gr_phy_write_2d        use phyetat0_m, only: itau_phy
       use gr_phy_write_3d_m, only: gr_phy_write_3d  
416    
417        logical, intent(in):: lessivage        logical, intent(in):: lessivage
       integer, intent(in):: itap ! number of calls to "physiq"  
       integer, intent(in):: nid_ins  
418    
419        ! Variables local to the procedure:        ! Variables local to the procedure:
420        integer it        integer it
# Line 428  contains Line 424  contains
424    
425        itau_w = itau_phy + itap        itau_w = itau_phy + itap
426    
427        CALL histwrite(nid_ins, "zmasse", itau_w, gr_phy_write_3d(zmasse))        CALL histwrite(nid_ins, "zmasse", itau_w, gr_phy_write(zmasse))
428    
429        DO it=1, nqmx - 2        DO it=1, nqmx - 2
430           CALL histwrite(nid_ins, tname(it+2), itau_w, &           CALL histwrite(nid_ins, tname(it+2), itau_w, &
431                gr_phy_write_3d(tr_seri(:, :, it)))                gr_phy_write(tr_seri(:, :, it)))
432           if (lessivage) THEN           if (lessivage) THEN
433              CALL histwrite(nid_ins, "fl"//tname(it+2), itau_w, &              CALL histwrite(nid_ins, "fl"//tname(it+2), itau_w, &
434                   gr_phy_write_3d(flestottr(:, :, it)))                   gr_phy_write(flestottr(:, :, it)))
435           endif           endif
436           CALL histwrite(nid_ins, "d_tr_th_"//tname(it+2), itau_w, &           CALL histwrite(nid_ins, "d_tr_th_"//tname(it+2), itau_w, &
437                gr_phy_write_3d(d_tr_th(:, :, it)))                gr_phy_write(d_tr_th(:, :, it)))
438           CALL histwrite(nid_ins, "d_tr_cv_"//tname(it+2), itau_w, &           CALL histwrite(nid_ins, "d_tr_cv_"//tname(it+2), itau_w, &
439                gr_phy_write_3d(d_tr_cv(:, :, it)))                gr_phy_write(d_tr_cv(:, :, it)))
440           CALL histwrite(nid_ins, "d_tr_cl_"//tname(it+2), itau_w, &           CALL histwrite(nid_ins, "d_tr_cl_"//tname(it+2), itau_w, &
441                gr_phy_write_3d(d_tr_cl(:, :, it)))                gr_phy_write(d_tr_cl(:, :, it)))
442        ENDDO        ENDDO
443    
444      end subroutine write_histrac      end subroutine write_histrac

Legend:
Removed from v.159  
changed lines
  Added in v.191

  ViewVC Help
Powered by ViewVC 1.1.21