/[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

trunk/libf/phylmd/phytrac.f90 revision 18 by guez, Thu Aug 7 12:29:13 2008 UTC trunk/Sources/phylmd/phytrac.f revision 182 by guez, Wed Mar 16 11:11:27 2016 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 9  module phytrac_m Line 7  module phytrac_m
7    
8  contains  contains
9    
10    SUBROUTINE phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, &    SUBROUTINE phytrac(itap, lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, &
11         nq_phys, pdtphys, u, v, t_seri, paprs, pplay, pmfu, pmfd, pen_u, &         t_seri, paprs, pplay, pmfu, pmfd, pde_u, pen_d, coefh, fm_therm, &
12         pde_u, pen_d, pde_d, coefh, fm_therm, entr_therm, yu1, yv1, ftsol, &         entr_therm, yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, da, phi, &
13         pctsrf, frac_impa, frac_nucl, presnivs, pphis, &         mp, upwd, dnwd, tr_seri, zmasse, ncid_startphy, nid_ins, itau_phy)
        pphi, albsol, rh, cldfra, rneb, diafra, cldliq, itop_con, &  
        ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, &  
        tr_seri, zmasse)  
14    
15      ! 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 (SVN revision 679)
16    
17      ! Authors: Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice      ! Authors: Fr\'ed\'eric Hourdin, Abderrahmane Idelkadi, Marie-Alice
18      ! Foujols, Olivia      ! Foujols, Olivia
     ! Objet : moniteur général des tendances des traceurs  
19    
20      ! Remarques :      ! Objet : moniteur g\'en\'eral des tendances des traceurs
21      ! 1/ L'appel de "phytrac" se fait avec "nq-2" donc nous avons bien  
22      ! les vrais traceurs (en nombre "nbtr", sans la vapeur d'eau ni l'eau      ! L'appel de "phytrac" se fait avec "nqmx - 2" donc nous avons
23      ! liquide) dans "phytrac".      ! bien les vrais traceurs, sans la vapeur d'eau ni l'eau liquide.
24      ! 2/ Le choix du radon et du plomb se fait juste avec un "data"  
25      ! (peu propre).      ! Modifications pour les traceurs :
26      ! Pourrait-on avoir une variable qui indiquerait le type de traceur ?      ! - uniformisation des parametrisations dans phytrac
27        ! - stockage des moyennes des champs n\'ecessaires en mode traceur off-line
28    
     use dimens_m, only: llm  
     use indicesol, only: nbsrf  
     use dimphy, only: klon, nbtr  
     use clesphys, only: ecrit_tra  
     use clesphys2, only: iflag_con  
29      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
30      use YOMCST, only: rg      use clesphys, only: ecrit_tra
31        use clesphys2, only: conv_emanuel
32        use cltrac_m, only: cltrac
33        use cltracrn_m, only: cltracrn
34      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
35      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz      use cvltr_m, only: cvltr
36      use phyetat0_m, only: rlat      use dimens_m, only: llm, nqmx
37      use o3_chem_m, only: o3_chem      use dimphy, only: klon
38      use ini_hist, only: ini_histrac      use indicesol, only: nbsrf
39      use radiornpb_m, only: radiornpb      use initrrnpb_m, only: initrrnpb
40      use minmaxqfi_m, only: minmaxqfi      use minmaxqfi_m, only: minmaxqfi
41      use numer_rec, only: assert      use netcdf, only: NF90_FILL_float
42        use netcdf95, only: nf95_inq_varid, nf95_get_var, nf95_put_var
43        use nflxtr_m, only: nflxtr
44        use nr_util, only: assert
45        use o3_chem_m, only: o3_chem
46        use phyetat0_m, only: rlat
47        use phyredem0_m, only: ncid_restartphy
48      use press_coefoz_m, only: press_coefoz      use press_coefoz_m, only: press_coefoz
49        use radiornpb_m, only: radiornpb
50        use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
51        use SUPHEC_M, only: rg
52    
53      ! Arguments:      integer, intent(in):: itap ! number of calls to "physiq"
   
     !   EN ENTREE:  
   
     !   divers:  
   
     logical, intent(in):: rnpb  
   
     integer, intent(in):: nq_phys  
     ! (nombre de traceurs auxquels on applique la physique)  
   
     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      integer itop_con(klon)      real, intent(in):: gmtime ! heure de la journ\'ee en fraction de jour
57      integer ibas_con(klon)      logical, intent(in):: firstcal ! first call to "calfis"
58      real, intent(in):: gmtime ! heure de la journée en fraction de jour      logical, intent(in):: lafin ! fin de la physique
59      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)      real, intent(in):: pdtphys ! pas d'integration pour la physique (s)
60      real, intent(in):: t_seri(klon, llm) ! temperature, in K      real, intent(in):: t_seri(klon, llm) ! temperature, in K
61    
     real, intent(inout):: tr_seri(:, :, :) ! (klon, llm, nbtr)  
     ! (mass fractions of tracers, excluding water, at mid-layers)  
   
     real u(klon, llm)  
     real v(klon, llm)  
     real rh(klon, llm)     ! humidite relative  
     real cldliq(klon, llm) ! eau liquide nuageuse  
     real cldfra(klon, llm) ! fraction nuageuse (tous les nuages)  
   
     real diafra(klon, llm)  
     ! (fraction nuageuse (convection ou stratus artificiels))  
   
     real rneb(klon, llm)   ! fraction nuageuse (grande echelle)  
     real albsol(klon)  ! albedo surface  
   
62      real, intent(in):: paprs(klon, llm+1)      real, intent(in):: paprs(klon, llm+1)
63      ! (pression pour chaque inter-couche, en Pa)      ! (pression pour chaque inter-couche, en Pa)
64    
65      real, intent(in):: pplay(klon, llm)      real, intent(in):: pplay(klon, llm)
66      ! (pression pour le mileu de chaque couche, en Pa)      ! (pression pour le mileu de chaque couche, en Pa)
67    
68      real pphi(klon, llm) ! geopotentiel      ! convection:
     real pphis(klon)  
     REAL, intent(in):: presnivs(llm)  
     logical, intent(in):: firstcal ! first call to "calfis"  
     logical, intent(in):: lafin ! fin de la physique  
   
     REAL pmflxr(klon, llm+1), pmflxs(klon, llm+1)   !--lessivage convection  
     REAL prfl(klon, llm+1),   psfl(klon, llm+1)     !--lessivage large-scale  
69    
70      !   convection:      REAL, intent(in):: pmfu(klon, llm) ! flux de masse dans le panache montant
     REAL pmfu(klon, llm)  ! flux de masse dans le panache montant  
     REAL pmfd(klon, llm)  ! flux de masse dans le panache descendant  
     REAL pen_u(klon, llm) ! flux entraine dans le panache montant  
71    
72      !   thermiques:      REAL, intent(in):: pmfd(klon, llm)
73        ! flux de masse dans le panache descendant
     real fm_therm(klon, llm+1), entr_therm(klon, llm)  
74    
75      REAL pde_u(klon, llm) ! flux detraine dans le panache montant      REAL pde_u(klon, llm) ! flux detraine dans le panache montant
76      REAL pen_d(klon, llm) ! flux entraine dans le panache descendant      REAL pen_d(klon, llm) ! flux entraine dans le panache descendant
77      REAL pde_d(klon, llm) ! flux detraine dans le panache descendant      REAL coefh(klon, llm) ! coeff melange couche limite
     ! KE  
     real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)  
     REAL upwd(klon, llm)      ! saturated updraft mass flux  
     REAL dnwd(klon, llm)      ! saturated downdraft mass flux  
78    
79      !   Couche limite:      ! thermiques:
80        real fm_therm(klon, llm+1), entr_therm(klon, llm)
     REAL coefh(klon, llm) ! coeff melange CL  
     REAL yu1(klon)        ! vents au premier niveau  
     REAL yv1(klon)        ! vents au premier niveau  
   
     !   Lessivage:  
81    
82      ! pour le ON-LINE      ! Couche limite:
83        REAL yu1(klon) ! vents au premier niveau
84        REAL yv1(klon) ! vents au premier niveau
85    
86      REAL frac_impa(klon, llm)  ! fraction d'aerosols impactes      ! Arguments n\'ecessaires pour les sources et puits de traceur :
87      REAL frac_nucl(klon, llm)  ! fraction d'aerosols nuclees      real, intent(in):: ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin)
88        real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)
89    
90      ! Arguments necessaires pour les sources et puits de traceur:      ! Lessivage pour le on-line
91        REAL frac_impa(klon, llm) ! fraction d'aerosols impactes
92        REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees
93    
94        ! Kerry Emanuel
95        real, intent(in):: da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
96        REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux
97        REAL, intent(in):: dnwd(klon, llm) ! saturated downdraft mass flux
98    
99      real ftsol(klon, nbsrf)  ! Temperature du sol (surf)(Kelvin)      real, intent(inout):: tr_seri(:, :, :) ! (klon, llm, nqmx - 2)
100      real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)      ! (mass fractions of tracers, excluding water, at mid-layers)
101    
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      ! Variables local to the procedure:      integer, intent(in):: ncid_startphy, nid_ins, itau_phy
106    
107        ! Local:
108    
109      integer nsplit      integer nsplit
110    
111      !  TRACEURS      ! TRACEURS
112    
113      ! Sources et puits des traceurs:      ! Sources et puits des traceurs:
114    
115      ! Pour l'instant seuls les cas du rn et du pb ont ete envisages.      ! Pour l'instant seuls les cas du rn et du pb ont ete envisages.
116    
117      REAL source(klon)       ! a voir lorsque le flux est prescrit      REAL source(klon) ! a voir lorsque le flux est prescrit
118      !      !
119      ! Pour la source de radon et son reservoir de sol      ! Pour la source de radon et son reservoir de sol
120    
121      REAL, save:: trs(klon, nbtr)    ! Concentration de radon dans le sol      REAL, save:: trs(klon, nqmx - 2) ! Concentration de traceur dans le sol
122    
123      REAL masktr(klon, nbtr) ! Masque reservoir de sol traceur      REAL masktr(klon, nqmx - 2) ! Masque reservoir de sol traceur
124      !                            Masque de l'echange avec la surface      ! Masque de l'echange avec la surface
125      !                           (1 = reservoir) ou (possible => 1 )      ! (1 = reservoir) ou (possible => 1)
126      SAVE masktr      SAVE masktr
127      REAL fshtr(klon, nbtr)  ! Flux surfacique dans le reservoir de sol      REAL fshtr(klon, nqmx - 2) ! Flux surfacique dans le reservoir de sol
128      SAVE fshtr      SAVE fshtr
129      REAL hsoltr(nbtr)      ! Epaisseur equivalente du reservoir de sol      REAL hsoltr(nqmx - 2) ! Epaisseur equivalente du reservoir de sol
130      SAVE hsoltr      SAVE hsoltr
131      REAL tautr(nbtr)       ! Constante de decroissance radioactive      REAL tautr(nqmx - 2) ! Constante de decroissance radioactive
132      SAVE tautr      SAVE tautr
133      REAL vdeptr(nbtr)      ! Vitesse de depot sec dans la couche Brownienne      REAL vdeptr(nqmx - 2) ! Vitesse de depot sec dans la couche Brownienne
134      SAVE vdeptr      SAVE vdeptr
135      REAL scavtr(nbtr)      ! Coefficient de lessivage      REAL scavtr(nqmx - 2) ! Coefficient de lessivage
136      SAVE scavtr      SAVE scavtr
137    
138      CHARACTER itn      CHARACTER itn
     INTEGER, save:: nid_tra  
139    
140      ! nature du traceur      ! nature du traceur
141    
142      logical aerosol(nbtr)  ! Nature du traceur      logical aerosol(nqmx - 2) ! Nature du traceur
143      !                            ! aerosol(it) = true  => aerosol      ! ! aerosol(it) = true => aerosol
144      !                            ! aerosol(it) = false => gaz      ! ! aerosol(it) = false => gaz
145      logical clsol(nbtr)    ! couche limite sol calculée      logical clsol(nqmx - 2) ! couche limite sol calcul\'ee
146      logical radio(nbtr)    ! décroisssance radioactive      logical radio(nqmx - 2) ! d\'ecroisssance radioactive
147      save aerosol, clsol, radio      save aerosol, clsol, radio
148    
149      ! convection tiedtke      ! convection tiedtke
# Line 188  contains Line 155  contains
155      ! Variables locales pour effectuer les appels en serie      ! Variables locales pour effectuer les appels en serie
156    
157      REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs      REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs
158      REAL d_tr_cl(klon, llm, nbtr) ! tendance de traceurs  couche limite      REAL d_tr_cl(klon, llm, nqmx - 2) ! tendance de traceurs couche limite
159      REAL d_tr_cv(klon, llm, nbtr) ! tendance de traceurs  conv pour chq traceur  
160      REAL d_tr_th(klon, llm, nbtr) ! la tendance des thermiques      REAL d_tr_cv(klon, llm, nqmx - 2)
161        ! tendance de traceurs conv pour chq traceur
162    
163        REAL d_tr_th(klon, llm, nqmx - 2) ! la tendance des thermiques
164      REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance      REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance
165      !                                   ! radioactive du rn - > pb      ! ! radioactive du rn - > pb
166      REAL d_tr_lessi_impa(klon, llm, nbtr) ! la tendance du lessivage      REAL d_tr_lessi_impa(klon, llm, nqmx - 2) ! la tendance du lessivage
167      !                                          ! par impaction      ! ! par impaction
168      REAL d_tr_lessi_nucl(klon, llm, nbtr) ! la tendance du lessivage      REAL d_tr_lessi_nucl(klon, llm, nqmx - 2) ! la tendance du lessivage
169      !                                          ! par nucleation      ! ! par nucleation
170      REAL flestottr(klon, llm, nbtr) ! flux de lessivage      REAL flestottr(klon, llm, nqmx - 2) ! flux de lessivage
171      !                                    ! dans chaque couche      ! ! dans chaque couche
172    
173      real ztra_th(klon, llm)      real ztra_th(klon, llm)
174      integer isplit      integer isplit, varid
175    
176      ! Controls:      ! Controls:
177      logical:: couchelimite = .true.      logical:: couchelimite = .true.
# Line 212  contains Line 182  contains
182      !--------------------------------------      !--------------------------------------
183    
184      call assert(shape(zmasse) == (/klon, llm/), "phytrac zmasse")      call assert(shape(zmasse) == (/klon, llm/), "phytrac zmasse")
185      call assert(shape(tr_seri) == (/klon, llm, nbtr/), "phytrac tr_seri")      call assert(shape(tr_seri) == (/klon, llm, nqmx - 2/), "phytrac tr_seri")
186    
187      if (firstcal) then      if (firstcal) then
188         print *, 'phytrac: pdtphys = ', pdtphys         print *, 'phytrac: pdtphys = ', pdtphys
189         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra         PRINT *, 'Frequency of tracer output: ecrit_tra = ', ecrit_tra
190         if (nbtr < nq_phys) call abort_gcm('phytrac', 'nbtr < nq_phys', 1)         inirnpb = .true.
        inirnpb=rnpb  
   
        ! Initialisation des sorties :  
        call ini_histrac(nid_tra, pdtphys, presnivs, nq_phys, lessivage)  
191    
192         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
193         ! Initialisation du traceur dans le sol (couche limite radonique)         ! Initialisation du traceur dans le sol (couche limite radonique)
194         trs(:, :) = 0.         trs(:, 2:) = 0.
195    
196         open (unit=99, file='starttrac', status='old', err=999, &         call nf95_inq_varid(ncid_startphy, "trs", varid)
197              form='formatted')         call nf95_get_var(ncid_startphy, varid, trs(:, 1))
198         read(unit=99, fmt=*) (trs(i, 1), i=1, klon)         if (any(trs(:, 1) == NF90_FILL_float)) call abort_gcm("phytrac", &
199  999    continue              "some missing values in trs(:, 1)")
        close(unit=99)  
200    
201         ! Initialisation de la fraction d'aerosols lessivee         ! Initialisation de la fraction d'aerosols lessivee
202    
203         d_tr_lessi_impa(:, :, :) = 0.         d_tr_lessi_impa = 0.
204         d_tr_lessi_nucl(:, :, :) = 0.         d_tr_lessi_nucl = 0.
205    
206         ! Initialisation de la nature des traceurs         ! Initialisation de la nature des traceurs
207    
208         DO it = 1, nq_phys         DO it = 1, nqmx - 2
209            aerosol(it) = .FALSE.  ! Tous les traceurs sont des gaz par defaut            aerosol(it) = .FALSE. ! Tous les traceurs sont des gaz par defaut
210            radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"            radio(it) = .FALSE. ! par d\'efaut pas de passage par "radiornpb"
211            clsol(it) = .FALSE.  ! Par defaut couche limite avec flux prescrit            clsol(it) = .FALSE. ! Par defaut couche limite avec flux prescrit
212         ENDDO         ENDDO
213    
214         if (nq_phys >= 3) then         if (nqmx >= 5) then
215            call press_coefoz ! read input pressure levels for ozone coefficients            call press_coefoz ! read input pressure levels for ozone coefficients
216         end if         end if
217      ENDIF      ENDIF
218    
     ! Initialisation du traceur dans le sol (couche limite radonique)  
219      if (inirnpb) THEN      if (inirnpb) THEN
220           ! Initialisation du traceur dans le sol (couche limite radonique)
221         radio(1)= .true.         radio(1)= .true.
222         radio(2)= .true.         radio(2)= .true.
223         clsol(1)= .true.         clsol(1)= .true.
224         clsol(2)= .true.         clsol(2)= .true.
225         aerosol(2) = .TRUE. ! le Pb est un aerosol         aerosol(2) = .TRUE. ! le Pb est un aerosol
226           call initrrnpb(pctsrf, masktr, fshtr, hsoltr, tautr, vdeptr, scavtr)
        call initrrnpb(ftsol, pctsrf, masktr, fshtr, hsoltr, tautr, vdeptr, &  
             scavtr)  
227         inirnpb=.false.         inirnpb=.false.
228      endif      endif
229    
     ! Calcul de l'effet de la convection  
   
230      if (convection) then      if (convection) then
231         DO it=1, nq_phys         ! Calcul de l'effet de la convection
232            if (iflag_con.eq.2) then         DO it=1, nqmx - 2
233               ! tiedke            if (conv_emanuel) then
234               CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &               call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, &
235                    paprs, tr_seri(1, 1, it), d_tr_cv(1, 1, it))                    dnwd, d_tr_cv(:, :, it))
236            else if (iflag_con.eq.3) then            else
237               ! KE               CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, &
238               call cvltr(pdtphys, da, phi, mp, paprs, &                    tr_seri(:, :, it), d_tr_cv(:, :, it))
                   tr_seri(1, 1, it), upwd, dnwd, d_tr_cv(1, 1, it))  
239            endif            endif
240    
241            DO k = 1, llm            DO k = 1, llm
# Line 285  contains Line 244  contains
244               ENDDO               ENDDO
245            ENDDO            ENDDO
246            WRITE(unit=itn, fmt='(i1)') it            WRITE(unit=itn, fmt='(i1)') it
247            CALL minmaxqfi(tr_seri(:, :, it), 0., 1.e33, &            CALL minmaxqfi(tr_seri(:, :, it), 0., 1e33, &
248                 'convection, tracer index = ' // itn)                 'convection, tracer index = ' // itn)
249         ENDDO         ENDDO
250      endif      endif
251    
252      ! Calcul de l'effet des thermiques      ! Calcul de l'effet des thermiques
253    
254      do it=1, nq_phys      do it=1, nqmx - 2
255         do k=1, llm         do k=1, llm
256            do i=1, klon            do i=1, klon
257               d_tr_th(i, k, it)=0.               d_tr_th(i, k, it)=0.
258               tr_seri(i, k, it)=max(tr_seri(i, k, it), 0.)               tr_seri(i, k, it)=max(tr_seri(i, k, it), 0.)
259               tr_seri(i, k, it)=min(tr_seri(i, k, it), 1.e10)               tr_seri(i, k, it)=min(tr_seri(i, k, it), 1e10)
260            enddo            enddo
261         enddo         enddo
262      enddo      enddo
263    
264      if (iflag_thermals > 0) then      if (iflag_thermals > 0) then
265         nsplit=10         nsplit=10
266         DO it=1, nq_phys         DO it=1, nqmx - 2
267            do isplit=1, nsplit            do isplit=1, nsplit
268               ! Thermiques               ! Thermiques
269               call dqthermcell(klon, llm, pdtphys/nsplit &               call dqthermcell(klon, llm, pdtphys/nsplit &
# Line 322  contains Line 281  contains
281         ENDDO         ENDDO
282      endif      endif
283    
284      !   Calcul de l'effet de la couche limite      ! Calcul de l'effet de la couche limite
285    
286      if (couchelimite) then      if (couchelimite) then
   
287         DO k = 1, llm         DO k = 1, llm
288            DO i = 1, klon            DO i = 1, klon
289               delp(i, k) = paprs(i, k)-paprs(i, k+1)               delp(i, k) = paprs(i, k)-paprs(i, k+1)
290            ENDDO            ENDDO
291         ENDDO         ENDDO
292    
293         ! MAF modif pour tenir compte du cas rnpb + traceur         ! MAF modif pour tenir compte du cas traceur
294         DO it=1, nq_phys         DO it=1, nqmx - 2
295            if (clsol(it)) then            if (clsol(it)) then
296               ! couche limite avec quantite dans le sol calculee               ! couche limite avec quantite dans le sol calculee
297               CALL cltracrn(it, pdtphys, yu1, yv1, &               CALL cltracrn(it, pdtphys, yu1, yv1, coefh, t_seri, ftsol, &
298                    coefh, t_seri, ftsol, pctsrf, &                    pctsrf, tr_seri(:, :, it), trs(:, it), paprs, pplay, delp, &
299                    tr_seri(1, 1, it), trs(1, it), &                    masktr(1, it), fshtr(1, it), hsoltr(it), tautr(it), &
300                    paprs, pplay, delp, &                    vdeptr(it), rlat, d_tr_cl(1, 1, it), d_trs)
                   masktr(1, it), fshtr(1, it), hsoltr(it), &  
                   tautr(it), vdeptr(it), &  
                   rlat, &  
                   d_tr_cl(1, 1, it), d_trs)  
301               DO k = 1, llm               DO k = 1, llm
302                  DO i = 1, klon                  DO i = 1, klon
303                     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)                     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)
304                  ENDDO                  ENDDO
305               ENDDO               ENDDO
306    
307               ! Traceur ds sol               trs(:, it) = trs(:, it) + d_trs
308              else
309               DO i = 1, klon               ! couche limite avec flux prescrit
                 trs(i, it) = trs(i, it) + d_trs(i)  
              END DO  
           else ! couche limite avec flux prescrit  
310               !MAF provisoire source / traceur a creer               !MAF provisoire source / traceur a creer
311               DO i=1, klon               DO i=1, klon
312                  source(i) = 0.0 ! pas de source, pour l'instant                  source(i) = 0. ! pas de source, pour l'instant
313               ENDDO               ENDDO
314    
315               CALL cltrac(pdtphys, coefh, t_seri, &               CALL cltrac(pdtphys, coefh, t_seri, tr_seri(:, :, it), source, &
316                    tr_seri(1, 1, it), source, &                    paprs, pplay, delp, d_tr_cl(1, 1, it))
                   paprs, pplay, delp, &  
                   d_tr_cl(1, 1, it))  
317               DO k = 1, llm               DO k = 1, llm
318                  DO i = 1, klon                  DO i = 1, klon
319                     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)                     tr_seri(i, k, it) = tr_seri(i, k, it) + d_tr_cl(i, k, it)
# Line 372  contains Line 321  contains
321               ENDDO               ENDDO
322            endif            endif
323         ENDDO         ENDDO
324        endif
325    
326      endif ! couche limite      ! Calcul de l'effet du puits radioactif
   
     !   Calcul de l'effet du puits radioactif  
327    
328      ! MAF il faudrait faire une modification pour passer dans radiornpb      ! MAF il faudrait faire une modification pour passer dans radiornpb
329      ! si radio=true mais pour l'instant radiornpb propre au cas rnpb      ! si radio=true
330      if (rnpb) then      d_tr_dec = radiornpb(tr_seri, pdtphys, tautr)
331         d_tr_dec(:, :, :) = radiornpb(tr_seri, pdtphys, tautr)      DO it = 1, nqmx - 2
332         DO it=1, nq_phys         if (radio(it)) then
333            if (radio(it)) then            tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)
334               tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)            WRITE(unit=itn, fmt='(i1)') it
335               WRITE(unit=itn, fmt='(i1)') it            CALL minmaxqfi(tr_seri(:, :, it), 0., 1e33, 'puits rn it='//itn)
336               CALL minmaxqfi(tr_seri(:, :, it), 0., 1.e33, 'puits rn it='//itn)         endif
337            endif      ENDDO
        ENDDO  
     endif ! rnpb decroissance  radioactive  
338    
339      if (nq_phys >= 3) then      if (nqmx >= 5) then
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 402  contains Line 348  contains
348      ! Calcul de l'effet de la precipitation      ! Calcul de l'effet de la precipitation
349    
350      IF (lessivage) THEN      IF (lessivage) THEN
351         d_tr_lessi_nucl(:, :, :) = 0.         d_tr_lessi_nucl = 0.
352         d_tr_lessi_impa(:, :, :) = 0.         d_tr_lessi_impa = 0.
353         flestottr(:, :, :) = 0.         flestottr = 0.
354    
355         ! tendance des aerosols nuclees et impactes         ! tendance des aerosols nuclees et impactes
356    
357         DO it = 1, nq_phys         DO it = 1, nqmx - 2
358            IF (aerosol(it)) THEN            IF (aerosol(it)) THEN
359               DO k = 1, llm               DO k = 1, llm
360                  DO i = 1, klon                  DO i = 1, klon
361                     d_tr_lessi_nucl(i, k, it) = d_tr_lessi_nucl(i, k, it) + &                     d_tr_lessi_nucl(i, k, it) = d_tr_lessi_nucl(i, k, it) + &
362                          ( 1 - frac_nucl(i, k) )*tr_seri(i, k, it)                          (1 - frac_nucl(i, k))*tr_seri(i, k, it)
363                     d_tr_lessi_impa(i, k, it) = d_tr_lessi_impa(i, k, it) + &                     d_tr_lessi_impa(i, k, it) = d_tr_lessi_impa(i, k, it) + &
364                          ( 1 - frac_impa(i, k) )*tr_seri(i, k, it)                          (1 - frac_impa(i, k))*tr_seri(i, k, it)
365                  ENDDO                  ENDDO
366               ENDDO               ENDDO
367            ENDIF            ENDIF
# Line 424  contains Line 370  contains
370         ! Mises a jour des traceurs + calcul des flux de lessivage         ! Mises a jour des traceurs + calcul des flux de lessivage
371         ! Mise a jour due a l'impaction et a la nucleation         ! Mise a jour due a l'impaction et a la nucleation
372    
373         DO it = 1, nq_phys         DO it = 1, nqmx - 2
374            IF (aerosol(it)) THEN            IF (aerosol(it)) THEN
375               DO k = 1, llm               DO k = 1, llm
376                  DO i = 1, klon                  DO i = 1, klon
377                     tr_seri(i, k, it)=tr_seri(i, k, it) &                     tr_seri(i, k, it) = tr_seri(i, k, it) * frac_impa(i, k) &
378                          *frac_impa(i, k)*frac_nucl(i, k)                          * frac_nucl(i, k)
379                  ENDDO                  ENDDO
380               ENDDO               ENDDO
381            ENDIF            ENDIF
# Line 437  contains Line 383  contains
383    
384         ! Flux lessivage total         ! Flux lessivage total
385    
386         DO it = 1, nq_phys         DO it = 1, nqmx - 2
387            DO k = 1, llm            DO k = 1, llm
388               DO i = 1, klon               DO i = 1, klon
389                  flestottr(i, k, it) = flestottr(i, k, it) - &                  flestottr(i, k, it) = flestottr(i, k, it) &
390                       ( d_tr_lessi_nucl(i, k, it)   + &                       - (d_tr_lessi_nucl(i, k, it) + d_tr_lessi_impa(i, k, it)) &
391                       d_tr_lessi_impa(i, k, it) ) * &                       * (paprs(i, k)-paprs(i, k+1)) / (RG * pdtphys)
                      ( paprs(i, k)-paprs(i, k+1) ) /  &  
                      (RG * pdtphys)  
392               ENDDO               ENDDO
393            ENDDO            ENDDO
394         ENDDO         ENDDO
395      ENDIF      ENDIF
396    
397      !   Ecriture des sorties      ! Ecriture des sorties
398      call write_histrac(lessivage, nq_phys, itap, nid_tra)      call write_histrac(lessivage, itap, nid_ins)
399    
400      if (lafin) then      if (lafin) then
401         print *, "C'est la fin de la physique."         call nf95_inq_varid(ncid_restartphy, "trs", varid)
402         open (unit=99, file='restarttrac',  form='formatted')         call nf95_put_var(ncid_restartphy, varid, trs(:, 1))
        do i=1, klon  
           write(unit=99, fmt=*) trs(i, 1)  
        enddo  
        PRINT *, 'Ecriture du fichier restarttrac'  
        close(99)  
403      endif      endif
404    
405    contains    contains
406    
407      subroutine write_histrac(lessivage, nq_phys, itap, nid_tra)      subroutine write_histrac(lessivage, itap, nid_ins)
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 histwrite_m, only: histwrite
412        use ioipsl, only: histwrite, histsync        use iniadvtrac_m, only: tname
413        use temps, only: itau_phy        use gr_phy_write_3d_m, only: gr_phy_write_3d
       use iniadvtrac_m, only: tnom  
       use comgeomphy, only: airephy  
       use dimphy, only: klon  
414    
415        logical, intent(in):: lessivage        logical, intent(in):: lessivage
416          integer, intent(in):: itap ! number of calls to "physiq"
417        integer, intent(in):: nq_phys        integer, intent(in):: nid_ins
       ! (nombre de traceurs auxquels on applique la physique)  
   
       integer, intent(in):: itap  ! number of calls to "physiq"  
       integer, intent(in):: nid_tra  
418    
419        ! Variables local to the procedure:        ! Variables local to the procedure:
420        integer it        integer it
421        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)  
       logical, parameter:: ok_sync = .true.  
422    
423        !-----------------------------------------------------        !-----------------------------------------------------
424    
425        itau_w = itau_phy + itap        itau_w = itau_phy + itap
426    
427        CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d)        CALL histwrite(nid_ins, "zmasse", itau_w, gr_phy_write_3d(zmasse))
       CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d)        
       CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d)  
428    
429        CALL gr_fi_ecrit(llm, klon, iim, jjm+1, zmasse, zx_tmp_3d)              DO it=1, nqmx - 2
430        CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d)           CALL histwrite(nid_ins, tname(it+2), itau_w, &
431                  gr_phy_write_3d(tr_seri(:, :, it)))
       DO it=1, nq_phys  
          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, zx_tmp_3d)  
432           if (lessivage) THEN           if (lessivage) THEN
433              CALL gr_fi_ecrit(llm, klon, iim, jjm+1, flestottr(1, 1, it), &              CALL histwrite(nid_ins, "fl"//tname(it+2), itau_w, &
434                   zx_tmp_3d)                   gr_phy_write_3d(flestottr(:, :, it)))
             CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d)  
435           endif           endif
436             CALL histwrite(nid_ins, "d_tr_th_"//tname(it+2), itau_w, &
437           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)))
438           CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, zx_tmp_3d)           CALL histwrite(nid_ins, "d_tr_cv_"//tname(it+2), itau_w, &
439           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)))
440           CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d)           CALL histwrite(nid_ins, "d_tr_cl_"//tname(it+2), itau_w, &
441           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)  
442        ENDDO        ENDDO
443    
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d)  
       CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d)  
   
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, t_seri, zx_tmp_3d)  
       CALL histwrite(nid_tra, "t", itau_w, zx_tmp_3d)  
   
       if (ok_sync) then  
          call histsync(nid_tra)  
       endif  
   
444      end subroutine write_histrac      end subroutine write_histrac
445    
446    END SUBROUTINE phytrac    END SUBROUTINE phytrac

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

  ViewVC Help
Powered by ViewVC 1.1.21