/[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 7 by guez, Mon Mar 31 12:24:17 2008 UTC trunk/Sources/phylmd/phytrac.f revision 201 by guez, Mon Jun 6 17:42:15 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(lmt_pas, julien, gmtime, firstcal, lafin, pdtphys, &
11         nqmax, 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)
14         pphi, albsol, sh, rh, cldfra, rneb, diafra, cldliq, itop_con, &  
15         ibas_con, pmflxr, pmflxs, prfl, psfl, da, phi, mp, upwd, dnwd, tr_seri)      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30 (SVN
16        ! revision 679) and phylmd/write_histrac.h, version 1.9 2006/02/21
17      ! From phylmd/phytrac.F, version 1.15 2006/02/21 08:08:30      ! 08:08:30
18    
19      ! Authors : Frédéric Hourdin, Abderrahmane Idelkadi, Marie-Alice      ! Authors: Fr\'ed\'eric Hourdin, Abderrahmane Idelkadi, Marie-Alice
20      ! Foujols, Olivia      ! Foujols, Olivia
     ! Objet : moniteur général des tendances des traceurs  
21    
22      ! Remarques :      ! Objet : moniteur g\'en\'eral des tendances des traceurs
23      ! 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      ! L'appel de "phytrac" se fait avec "nqmx - 2" donc nous avons
25      ! liquide) dans "phytrac".      ! bien les vrais traceurs, sans la vapeur d'eau ni l'eau liquide.
26      ! 2/ Le choix du radon et du plomb se fait juste avec un "data"  
27      ! (peu propre).      ! Modifications pour les traceurs :
28      ! Pourrait-on avoir une variable qui indiquerait le type de traceur ?      ! - uniformisation des parametrisations dans phytrac
29        ! - stockage des moyennes des champs n\'ecessaires en mode traceur off-line
30    
     use dimens_m, only: iim, jjm, llm  
     use indicesol, only: nbsrf  
     use dimphy, only: klon, nbtr  
     use clesphys, only: ecrit_tra, iflag_con  
31      use abort_gcm_m, only: abort_gcm      use abort_gcm_m, only: abort_gcm
32      use YOMCST, only: rg      use clesphys, only: ecrit_tra
33        use clesphys2, only: conv_emanuel
34        use cltrac_m, only: cltrac
35        use cltracrn_m, only: cltracrn
36      use ctherm, only: iflag_thermals      use ctherm, only: iflag_thermals
37      use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz      use cvltr_m, only: cvltr
38      use phyetat0_m, only: rlat      use dimens_m, only: llm, nqmx
39        use dimphy, only: klon
40        use histwrite_phy_m, only: histwrite_phy
41        use indicesol, only: nbsrf
42        use iniadvtrac_m, only: tname
43        use initrrnpb_m, only: initrrnpb
44        use minmaxqfi_m, only: minmaxqfi
45        use netcdf, only: NF90_FILL_float
46        use netcdf95, only: nf95_inq_varid, nf95_get_var, nf95_put_var
47        use nflxtr_m, only: nflxtr
48        use nr_util, only: assert
49      use o3_chem_m, only: o3_chem      use o3_chem_m, only: o3_chem
50        use phyetat0_m, only: rlat
51        use phyredem0_m, only: ncid_restartphy
52        use press_coefoz_m, only: press_coefoz
53        use radiornpb_m, only: radiornpb
54        use regr_pr_comb_coefoz_m, only: regr_pr_comb_coefoz
55        use SUPHEC_M, only: rg
56        use time_phylmdz, only: itap
57    
     ! Arguments:  
   
     !   EN ENTREE:  
   
     !   divers:  
   
     logical, intent(in):: rnpb  
   
     integer, intent(in):: nqmax  
     ! (nombre de traceurs auxquels on applique la physique)  
   
     integer, intent(in):: itap  ! number of calls to "physiq"  
58      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
59      integer, intent(in):: julien !jour julien, 1 <= julien <= 360      integer, intent(in):: julien !jour julien, 1 <= julien <= 360
60      integer itop_con(klon)      real, intent(in):: gmtime ! heure de la journ\'ee en fraction de jour
61      integer ibas_con(klon)      logical, intent(in):: firstcal ! first call to "calfis"
62      real, intent(in):: gmtime ! heure de la journée en fraction de jour      logical, intent(in):: lafin ! fin de la physique
63      real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)      real, intent(in):: pdtphys ! pas d'integration pour la physique (s)
64      real, intent(in):: t_seri(klon, llm) ! temperature, in K      real, intent(in):: t_seri(klon, llm) ! temperature, in K
65    
     real tr_seri(klon, llm, nbtr)  
     ! (mass fractions of tracers, excluding water, at mid-layers)  
   
     real u(klon, llm)  
     real v(klon, llm)  
     real sh(klon, llm)     ! humidite specifique  
     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  
   
66      real, intent(in):: paprs(klon, llm+1)      real, intent(in):: paprs(klon, llm+1)
67      ! (pression pour chaque inter-couche, en Pa)      ! (pression pour chaque inter-couche, en Pa)
68    
69      real pplay(klon, llm)  ! pression pour le mileu de chaque couche (en Pa)      real, intent(in):: pplay(klon, llm)
70      real pphi(klon, llm) ! geopotentiel      ! (pression pour le mileu de chaque couche, en Pa)
     real pphis(klon)  
     REAL, intent(in):: presnivs(llm)  
     logical, intent(in):: firstcal ! first call to "calfis"  
     logical, intent(in):: lafin ! fin de la physique  
71    
72      integer nsplit      ! convection:
     REAL pmflxr(klon, llm+1), pmflxs(klon, llm+1)   !--lessivage convection  
     REAL prfl(klon, llm+1),   psfl(klon, llm+1)     !--lessivage large-scale  
   
     !   convection:  
73    
74      REAL pmfu(klon, llm)  ! flux de masse dans le panache montant      REAL, intent(in):: 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  
75    
76      !   thermiques:      REAL, intent(in):: pmfd(klon, llm)
77        ! flux de masse dans le panache descendant
     real fm_therm(klon, llm+1), entr_therm(klon, llm)  
78    
79      REAL pde_u(klon, llm) ! flux detraine dans le panache montant      REAL pde_u(klon, llm) ! flux detraine dans le panache montant
80      REAL pen_d(klon, llm) ! flux entraine dans le panache descendant      REAL pen_d(klon, llm) ! flux entraine dans le panache descendant
81      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  
82    
83      !   Couche limite:      ! thermiques:
84        real fm_therm(klon, llm+1), entr_therm(klon, llm)
85    
86      REAL coefh(klon, llm) ! coeff melange CL      ! Couche limite:
87      REAL yu1(klon)        ! vents au premier niveau      REAL yu1(klon) ! vents au premier niveau
88      REAL yv1(klon)        ! vents au premier niveau      REAL yv1(klon) ! vents au premier niveau
89    
90      !   Lessivage:      ! Arguments n\'ecessaires pour les sources et puits de traceur :
91        real, intent(in):: ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin)
92        real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)
93    
94      ! pour le ON-LINE      ! Lessivage pour le on-line
95        REAL frac_impa(klon, llm) ! fraction d'aerosols impactes
96        REAL frac_nucl(klon, llm) ! fraction d'aerosols nuclees
97    
98        ! Kerry Emanuel
99        real, intent(in):: da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
100        REAL, intent(in):: upwd(klon, llm) ! saturated updraft mass flux
101        REAL, intent(in):: dnwd(klon, llm) ! saturated downdraft mass flux
102    
103      REAL frac_impa(klon, llm)  ! fraction d'aerosols impactes      real, intent(inout):: tr_seri(:, :, :) ! (klon, llm, nqmx - 2)
104      REAL frac_nucl(klon, llm)  ! fraction d'aerosols nuclees      ! (mass fractions of tracers, excluding water, at mid-layers)
105    
106      ! Arguments necessaires pour les sources et puits de traceur:      real, intent(in):: zmasse(:, :) ! (klon, llm)
107        ! (column-density of mass of air in a cell, in kg m-2)
108    
109      real ftsol(klon, nbsrf)  ! Temperature du sol (surf)(Kelvin)      integer, intent(in):: ncid_startphy
110      real pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)  
111        ! Local:
112    
113      real pftsol1(klon), pftsol2(klon), pftsol3(klon), pftsol4(klon)      integer nsplit
     real ppsrf1(klon), ppsrf2(klon), ppsrf3(klon), ppsrf4(klon)  
114    
115      !  VARIABLES LOCALES TRACEURS      ! TRACEURS
116    
117      ! Sources et puits des traceurs:      ! Sources et puits des traceurs:
118    
119      ! 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.
120    
121      REAL source(klon)       ! a voir lorsque le flux est prescrit      REAL source(klon) ! a voir lorsque le flux est prescrit
122      !      !
123      ! Pour la source de radon et son reservoir de sol      ! Pour la source de radon et son reservoir de sol
124    
125      REAL, save:: trs(klon, nbtr)    ! Concentration de radon dans le sol      REAL, save:: trs(klon, nqmx - 2) ! Concentration de traceur dans le sol
126    
127      REAL masktr(klon, nbtr) ! Masque reservoir de sol traceur      REAL masktr(klon, nqmx - 2) ! Masque reservoir de sol traceur
128      !                            Masque de l'echange avec la surface      ! Masque de l'echange avec la surface
129      !                           (1 = reservoir) ou (possible => 1 )      ! (1 = reservoir) ou (possible => 1)
130      SAVE masktr      SAVE masktr
131      REAL fshtr(klon, nbtr)  ! Flux surfacique dans le reservoir de sol      REAL fshtr(klon, nqmx - 2) ! Flux surfacique dans le reservoir de sol
132      SAVE fshtr      SAVE fshtr
133      REAL hsoltr(nbtr)      ! Epaisseur equivalente du reservoir de sol      REAL hsoltr(nqmx - 2) ! Epaisseur equivalente du reservoir de sol
134      SAVE hsoltr      SAVE hsoltr
135      REAL tautr(nbtr)       ! Constante de decroissance radioactive      REAL tautr(nqmx - 2) ! Constante de decroissance radioactive
136      SAVE tautr      SAVE tautr
137      REAL vdeptr(nbtr)      ! Vitesse de depot sec dans la couche Brownienne      REAL vdeptr(nqmx - 2) ! Vitesse de depot sec dans la couche Brownienne
138      SAVE vdeptr      SAVE vdeptr
139      REAL scavtr(nbtr)      ! Coefficient de lessivage      REAL scavtr(nqmx - 2) ! Coefficient de lessivage
140      SAVE scavtr      SAVE scavtr
141    
142      CHARACTER itn      CHARACTER itn
     INTEGER, save:: nid_tra  
143    
144      ! nature du traceur      ! nature du traceur
145    
146      logical aerosol(nbtr)  ! Nature du traceur      logical aerosol(nqmx - 2) ! Nature du traceur
147      !                            ! aerosol(it) = true  => aerosol      ! ! aerosol(it) = true => aerosol
148      !                            ! aerosol(it) = false => gaz      ! ! aerosol(it) = false => gaz
149      logical clsol(nbtr)    ! couche limite sol calculée      logical clsol(nqmx - 2) ! couche limite sol calcul\'ee
150      logical radio(nbtr)    ! décroisssance radioactive      logical radio(nqmx - 2) ! d\'ecroisssance radioactive
151      save aerosol, clsol, radio      save aerosol, clsol, radio
152    
153      ! convection tiedtke      ! convection tiedtke
# Line 178  contains Line 159  contains
159      ! Variables locales pour effectuer les appels en serie      ! Variables locales pour effectuer les appels en serie
160    
161      REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs      REAL d_tr(klon, llm), d_trs(klon) ! tendances de traceurs
162      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
     REAL d_tr_cv(klon, llm, nbtr) ! tendance de traceurs  conv pour chq traceur  
     REAL d_tr_th(klon, llm, nbtr) ! la tendance des thermiques  
     REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance  
     !                                   ! radioactive du rn - > pb  
     REAL d_tr_lessi_impa(klon, llm, nbtr) ! la tendance du lessivage  
     !                                          ! par impaction  
     REAL d_tr_lessi_nucl(klon, llm, nbtr) ! la tendance du lessivage  
     !                                          ! par nucleation  
     REAL flestottr(klon, llm, nbtr) ! flux de lessivage  
     !                                    ! dans chaque couche  
163    
164      real zmasse(klon, llm)      REAL d_tr_cv(klon, llm, nqmx - 2)
165      ! (column-density of mass of air in a layer, in kg m-2)      ! tendance de traceurs conv pour chq traceur
166    
167      real ztra_th(klon, llm)      REAL d_tr_th(klon, llm, nqmx - 2) ! la tendance des thermiques
168        REAL d_tr_dec(klon, llm, 2) ! la tendance de la decroissance
169        ! ! radioactive du rn - > pb
170        REAL d_tr_lessi_impa(klon, llm, nqmx - 2) ! la tendance du lessivage
171        ! ! par impaction
172        REAL d_tr_lessi_nucl(klon, llm, nqmx - 2) ! la tendance du lessivage
173        ! ! par nucleation
174        REAL flestottr(klon, llm, nqmx - 2) ! flux de lessivage
175        ! ! dans chaque couche
176    
177      character(len=20) modname      real ztra_th(klon, llm)
178      character(len=80) abort_message      integer isplit, varid
     integer isplit  
179    
180      ! Controls:      ! Controls:
181      logical:: couchelimite = .true.      logical:: couchelimite = .true.
# Line 207  contains Line 185  contains
185    
186      !--------------------------------------      !--------------------------------------
187    
188      modname='phytrac'      call assert(shape(zmasse) == (/klon, llm/), "phytrac zmasse")
189        call assert(shape(tr_seri) == (/klon, llm, nqmx - 2/), "phytrac tr_seri")
190    
191      if (firstcal) then      if (firstcal) then
192         print *, 'phytrac: pdtphys = ', pdtphys         print *, 'phytrac: pdtphys = ', pdtphys
193         PRINT *, 'Fréquence de sortie des traceurs : ecrit_tra = ', ecrit_tra         PRINT *, 'Frequency of tracer output: ecrit_tra = ', ecrit_tra
194         if (nbtr < nqmax) then         inirnpb = .true.
           abort_message='See above'  
           call abort_gcm(modname, abort_message, 1)  
        endif  
        inirnpb=rnpb  
   
        ! Initialisation des sorties :  
        call ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage)  
195    
196         ! Initialisation de certaines variables pour le radon et le plomb         ! Initialisation de certaines variables pour le radon et le plomb
197         ! Initialisation du traceur dans le sol (couche limite radonique)         ! Initialisation du traceur dans le sol (couche limite radonique)
198         trs(:, :) = 0.         trs(:, 2:) = 0.
199    
200         open (unit=99, file='starttrac', status='old', err=999, &         call nf95_inq_varid(ncid_startphy, "trs", varid)
201              form='formatted')         call nf95_get_var(ncid_startphy, varid, trs(:, 1))
202         read(unit=99, fmt=*) (trs(i, 1), i=1, klon)         if (any(trs(:, 1) == NF90_FILL_float)) call abort_gcm("phytrac", &
203  999    continue              "some missing values in trs(:, 1)")
        close(unit=99)  
204    
205         ! Initialisation de la fraction d'aerosols lessivee         ! Initialisation de la fraction d'aerosols lessivee
206    
207         d_tr_lessi_impa(:, :, :) = 0.         d_tr_lessi_impa = 0.
208         d_tr_lessi_nucl(:, :, :) = 0.         d_tr_lessi_nucl = 0.
209    
210         ! Initialisation de la nature des traceurs         ! Initialisation de la nature des traceurs
211    
212         DO it = 1, nqmax         DO it = 1, nqmx - 2
213            aerosol(it) = .FALSE.  ! Tous les traceurs sont des gaz par defaut            aerosol(it) = .FALSE. ! Tous les traceurs sont des gaz par defaut
214            radio(it) = .FALSE. ! par défaut pas de passage par "radiornpb"            radio(it) = .FALSE. ! par d\'efaut pas de passage par "radiornpb"
215            clsol(it) = .FALSE.  ! Par defaut couche limite avec flux prescrit            clsol(it) = .FALSE. ! Par defaut couche limite avec flux prescrit
216         ENDDO         ENDDO
217    
218           if (nqmx >= 5) then
219              call press_coefoz ! read input pressure levels for ozone coefficients
220           end if
221      ENDIF      ENDIF
222    
     ! Initialisation du traceur dans le sol (couche limite radonique)  
223      if (inirnpb) THEN      if (inirnpb) THEN
224           ! Initialisation du traceur dans le sol (couche limite radonique)
225         radio(1)= .true.         radio(1)= .true.
226         radio(2)= .true.         radio(2)= .true.
227         clsol(1)= .true.         clsol(1)= .true.
228         clsol(2)= .true.         clsol(2)= .true.
229         aerosol(2) = .TRUE. ! le Pb est un aerosol         aerosol(2) = .TRUE. ! le Pb est un aerosol
230           call initrrnpb(pctsrf, masktr, fshtr, hsoltr, tautr, vdeptr, scavtr)
        call initrrnpb(ftsol, pctsrf, masktr, fshtr, hsoltr, tautr, vdeptr, &  
             scavtr)  
231         inirnpb=.false.         inirnpb=.false.
232      endif      endif
233    
     do i=1, klon  
        pftsol1(i) = ftsol(i, 1)  
        pftsol2(i) = ftsol(i, 2)  
        pftsol3(i) = ftsol(i, 3)  
        pftsol4(i) = ftsol(i, 4)  
   
        ppsrf1(i) = pctsrf(i, 1)  
        ppsrf2(i) = pctsrf(i, 2)  
        ppsrf3(i) = pctsrf(i, 3)  
        ppsrf4(i) = pctsrf(i, 4)  
   
     enddo  
   
     ! Calcul de l'effet de la convection  
   
234      if (convection) then      if (convection) then
235         DO it=1, nqmax         ! Calcul de l'effet de la convection
236            if (iflag_con.eq.2) then         DO it=1, nqmx - 2
237               ! tiedke            if (conv_emanuel) then
238               CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &               call cvltr(pdtphys, da, phi, mp, paprs, tr_seri(:, :, it), upwd, &
239                    pplay, paprs, tr_seri(1, 1, it), d_tr_cv(1, 1, it))                    dnwd, d_tr_cv(:, :, it))
240            else if (iflag_con.eq.3) then            else
241               ! KE               CALL nflxtr(pdtphys, pmfu, pmfd, pde_u, pen_d, paprs, &
242               call cvltr(pdtphys, da, phi, mp, paprs, pplay, &                    tr_seri(:, :, it), d_tr_cv(:, :, it))
                   tr_seri(1, 1, it), upwd, dnwd, d_tr_cv(1, 1, it))  
243            endif            endif
244    
245            DO k = 1, llm            DO k = 1, llm
# Line 292  contains Line 248  contains
248               ENDDO               ENDDO
249            ENDDO            ENDDO
250            WRITE(unit=itn, fmt='(i1)') it            WRITE(unit=itn, fmt='(i1)') it
251            CALL minmaxqfi(tr_seri(:, :, it), 0., 1.e33, &            CALL minmaxqfi(tr_seri(:, :, it), 0., 1e33, &
252                 'convection, tracer index = ' // itn)                 'convection, tracer index = ' // itn)
253         ENDDO         ENDDO
254      endif      endif
255    
     forall (k=1: llm) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg  
   
256      ! Calcul de l'effet des thermiques      ! Calcul de l'effet des thermiques
257    
258      do it=1, nqmax      do it=1, nqmx - 2
259         do k=1, llm         do k=1, llm
260            do i=1, klon            do i=1, klon
261               d_tr_th(i, k, it)=0.               d_tr_th(i, k, it)=0.
262               tr_seri(i, k, it)=max(tr_seri(i, k, it), 0.)               tr_seri(i, k, it)=max(tr_seri(i, k, it), 0.)
263               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)
264            enddo            enddo
265         enddo         enddo
266      enddo      enddo
267    
268      if (iflag_thermals > 0) then      if (iflag_thermals > 0) then
269         nsplit=10         nsplit=10
270         DO it=1, nqmax         DO it=1, nqmx - 2
271            do isplit=1, nsplit            do isplit=1, nsplit
272               ! Thermiques               ! Thermiques
273               call dqthermcell(klon, llm, pdtphys/nsplit &               call dqthermcell(klon, llm, pdtphys/nsplit &
# Line 331  contains Line 285  contains
285         ENDDO         ENDDO
286      endif      endif
287    
288      !   Calcul de l'effet de la couche limite      ! Calcul de l'effet de la couche limite
289    
290      if (couchelimite) then      if (couchelimite) then
   
291         DO k = 1, llm         DO k = 1, llm
292            DO i = 1, klon            DO i = 1, klon
293               delp(i, k) = paprs(i, k)-paprs(i, k+1)               delp(i, k) = paprs(i, k)-paprs(i, k+1)
294            ENDDO            ENDDO
295         ENDDO         ENDDO
296    
297         ! MAF modif pour tenir compte du cas rnpb + traceur         ! MAF modif pour tenir compte du cas traceur
298         DO it=1, nqmax         DO it=1, nqmx - 2
299            if (clsol(it)) then            if (clsol(it)) then
300               ! couche limite avec quantite dans le sol calculee               ! couche limite avec quantite dans le sol calculee
301               CALL cltracrn(it, pdtphys, yu1, yv1, &               CALL cltracrn(it, pdtphys, yu1, yv1, coefh, t_seri, ftsol, &
302                    coefh, t_seri, ftsol, pctsrf, &                    pctsrf, tr_seri(:, :, it), trs(:, it), paprs, pplay, delp, &
303                    tr_seri(1, 1, it), trs(1, it), &                    masktr(1, it), fshtr(1, it), hsoltr(it), tautr(it), &
304                    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)  
305               DO k = 1, llm               DO k = 1, llm
306                  DO i = 1, klon                  DO i = 1, klon
307                     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)
308                  ENDDO                  ENDDO
309               ENDDO               ENDDO
310    
311               ! Traceur ds sol               trs(:, it) = trs(:, it) + d_trs
312              else
313               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  
314               !MAF provisoire source / traceur a creer               !MAF provisoire source / traceur a creer
315               DO i=1, klon               DO i=1, klon
316                  source(i) = 0.0 ! pas de source, pour l'instant                  source(i) = 0. ! pas de source, pour l'instant
317               ENDDO               ENDDO
318    
319               CALL cltrac(pdtphys, coefh, t_seri, &               CALL cltrac(pdtphys, coefh, t_seri, tr_seri(:, :, it), source, &
320                    tr_seri(1, 1, it), source, &                    paprs, pplay, delp, d_tr_cl(1, 1, it))
                   paprs, pplay, delp, &  
                   d_tr_cl(1, 1, it))  
321               DO k = 1, llm               DO k = 1, llm
322                  DO i = 1, klon                  DO i = 1, klon
323                     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 381  contains Line 325  contains
325               ENDDO               ENDDO
326            endif            endif
327         ENDDO         ENDDO
328        endif
329    
330      endif ! couche limite      ! Calcul de l'effet du puits radioactif
   
     !   Calcul de l'effet du puits radioactif  
331    
332      ! MAF il faudrait faire une modification pour passer dans radiornpb      ! MAF il faudrait faire une modification pour passer dans radiornpb
333      ! si radio=true mais pour l'instant radiornpb propre au cas rnpb      ! si radio=true
334      if (rnpb) then      d_tr_dec = radiornpb(tr_seri, pdtphys, tautr)
335         d_tr_dec(:, :, :) = radiornpb(tr_seri, pdtphys, tautr)      DO it = 1, nqmx - 2
336         DO it=1, nqmax         if (radio(it)) then
337            if (radio(it)) then            tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)
338               tr_seri(:, :, it) = tr_seri(:, :, it) + d_tr_dec(:, :, it)            WRITE(unit=itn, fmt='(i1)') it
339               WRITE(unit=itn, fmt='(i1)') it            CALL minmaxqfi(tr_seri(:, :, it), 0., 1e33, 'puits rn it='//itn)
340               CALL minmaxqfi(tr_seri(:, :, it), 0., 1.e33, 'puits rn it='//itn)         endif
341            endif      ENDDO
        ENDDO  
     endif ! rnpb decroissance  radioactive  
342    
343      if (nqmax >= 3) then      if (nqmx >= 5) then
344         ! Ozone as a tracer:         ! Ozone as a tracer:
345         if (mod(itap - 1, lmt_pas) == 0) then         if (mod(itap - 1, lmt_pas) == 0) then
346            ! Once per day, update the coefficients for ozone chemistry:            ! Once per day, update the coefficients for ozone chemistry:
347            call regr_pr_comb_coefoz(julien)            call regr_pr_comb_coefoz(julien, paprs, pplay)
348         end if         end if
349         call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))         call o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, tr_seri(:, :, 3))
350      end if      end if
# Line 411  contains Line 352  contains
352      ! Calcul de l'effet de la precipitation      ! Calcul de l'effet de la precipitation
353    
354      IF (lessivage) THEN      IF (lessivage) THEN
355         d_tr_lessi_nucl(:, :, :) = 0.         d_tr_lessi_nucl = 0.
356         d_tr_lessi_impa(:, :, :) = 0.         d_tr_lessi_impa = 0.
357         flestottr(:, :, :) = 0.         flestottr = 0.
358    
359         ! tendance des aerosols nuclees et impactes         ! tendance des aerosols nuclees et impactes
360    
361         DO it = 1, nqmax         DO it = 1, nqmx - 2
362            IF (aerosol(it)) THEN            IF (aerosol(it)) THEN
363               DO k = 1, llm               DO k = 1, llm
364                  DO i = 1, klon                  DO i = 1, klon
365                     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) + &
366                          ( 1 - frac_nucl(i, k) )*tr_seri(i, k, it)                          (1 - frac_nucl(i, k))*tr_seri(i, k, it)
367                     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) + &
368                          ( 1 - frac_impa(i, k) )*tr_seri(i, k, it)                          (1 - frac_impa(i, k))*tr_seri(i, k, it)
369                  ENDDO                  ENDDO
370               ENDDO               ENDDO
371            ENDIF            ENDIF
# Line 433  contains Line 374  contains
374         ! Mises a jour des traceurs + calcul des flux de lessivage         ! Mises a jour des traceurs + calcul des flux de lessivage
375         ! Mise a jour due a l'impaction et a la nucleation         ! Mise a jour due a l'impaction et a la nucleation
376    
377         DO it = 1, nqmax         DO it = 1, nqmx - 2
378            IF (aerosol(it)) THEN            IF (aerosol(it)) THEN
379               DO k = 1, llm               DO k = 1, llm
380                  DO i = 1, klon                  DO i = 1, klon
381                     tr_seri(i, k, it)=tr_seri(i, k, it) &                     tr_seri(i, k, it) = tr_seri(i, k, it) * frac_impa(i, k) &
382                          *frac_impa(i, k)*frac_nucl(i, k)                          * frac_nucl(i, k)
383                  ENDDO                  ENDDO
384               ENDDO               ENDDO
385            ENDIF            ENDIF
# Line 446  contains Line 387  contains
387    
388         ! Flux lessivage total         ! Flux lessivage total
389    
390         DO it = 1, nqmax         DO it = 1, nqmx - 2
391            DO k = 1, llm            DO k = 1, llm
392               DO i = 1, klon               DO i = 1, klon
393                  flestottr(i, k, it) = flestottr(i, k, it) - &                  flestottr(i, k, it) = flestottr(i, k, it) &
394                       ( d_tr_lessi_nucl(i, k, it)   + &                       - (d_tr_lessi_nucl(i, k, it) + d_tr_lessi_impa(i, k, it)) &
395                       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)  
396               ENDDO               ENDDO
397            ENDDO            ENDDO
398         ENDDO         ENDDO
399      ENDIF      ENDIF
400    
401      !   Ecriture des sorties      ! Ecriture des sorties
402      call write_histrac(lessivage, nqmax, itap, nid_tra)      CALL histwrite_phy("zmasse", zmasse)
403        DO it=1, nqmx - 2
404      if (lafin) then         CALL histwrite_phy(tname(it+2), tr_seri(:, :, it))
        print *, "C'est la fin de la physique."  
        open (unit=99, file='restarttrac',  form='formatted')  
        do i=1, klon  
           write(unit=99, fmt=*) trs(i, 1)  
        enddo  
        PRINT *, 'Ecriture du fichier restarttrac'  
        close(99)  
     endif  
   
   contains  
   
     subroutine write_histrac(lessivage, nqmax, itap, nid_tra)  
   
       ! From phylmd/write_histrac.h, version 1.9 2006/02/21 08:08:30  
   
       use dimens_m, only: iim, jjm, llm  
       use ioipsl, only: histwrite, histsync  
       use temps, only: itau_phy  
       use advtrac_m, only: tnom  
       use comgeomphy, only: airephy  
       use dimphy, only: klon  
   
       logical, intent(in):: lessivage  
   
       integer, intent(in):: nqmax  
       ! (nombre de traceurs auxquels on applique la physique)  
   
       integer, intent(in):: itap  ! number of calls to "physiq"  
       integer, intent(in):: nid_tra  
   
       ! Variables local to the procedure:  
       INTEGER ndex2d(iim*(jjm+1)), ndex3d(iim*(jjm+1)*llm)  
       integer it  
       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.  
   
       !-----------------------------------------------------  
   
       ndex2d = 0  
       ndex3d = 0  
       itau_w = itau_phy + itap  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d)  
       CALL histwrite(nid_tra, "phis", itau_w, zx_tmp_2d, iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, airephy, zx_tmp_2d)        
       CALL histwrite(nid_tra, "aire", itau_w, zx_tmp_2d, iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, zmasse, zx_tmp_3d)        
       CALL histwrite(nid_tra, "zmasse", itau_w, zx_tmp_3d, iim*(jjm+1)*llm, &  
            ndex3d)  
   
       DO it=1, nqmax  
          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, &  
               iim*(jjm+1)*llm, ndex3d)  
          if (lessivage) THEN  
             CALL gr_fi_ecrit(llm, klon, iim, jjm+1, flestottr(1, 1, it), &  
                  zx_tmp_3d)  
             CALL histwrite(nid_tra, "fl"//tnom(it+2), itau_w, zx_tmp_3d, &  
                  iim*(jjm+1)*llm, ndex3d)  
          endif  
   
          CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_th(1, 1, it), zx_tmp_3d)  
          CALL histwrite(nid_tra, "d_tr_th_"//tnom(it+2), itau_w, zx_tmp_3d, &  
               iim*(jjm+1)*llm, ndex3d)  
          CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cv(1, 1, it), zx_tmp_3d)  
          CALL histwrite(nid_tra, "d_tr_cv_"//tnom(it+2), itau_w, zx_tmp_3d, &  
               iim*(jjm+1)*llm, ndex3d)  
          CALL gr_fi_ecrit(llm, klon, iim, jjm+1, d_tr_cl(1, 1, it), zx_tmp_3d)  
          CALL histwrite(nid_tra, "d_tr_cl_"//tnom(it+2), itau_w, zx_tmp_3d, &  
               iim*(jjm+1)*llm, ndex3d)  
       ENDDO  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, yu1, zx_tmp_2d)  
       CALL histwrite(nid_tra, "pyu1", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, yv1, zx_tmp_2d)  
       CALL histwrite(nid_tra, "pyv1", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol1, zx_tmp_2d)  
       CALL histwrite(nid_tra, "ftsol1", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol2, zx_tmp_2d)  
       CALL histwrite(nid_tra, "ftsol2", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol3, zx_tmp_2d)  
       CALL histwrite(nid_tra, "ftsol3", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol4, zx_tmp_2d)  
       CALL histwrite(nid_tra, "ftsol4", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf1, zx_tmp_2d)  
       CALL histwrite(nid_tra, "psrf1", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf2, zx_tmp_2d)  
       CALL histwrite(nid_tra, "psrf2", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf3, zx_tmp_2d)  
       CALL histwrite(nid_tra, "psrf3", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
   
       CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf4, zx_tmp_2d)  
       CALL histwrite(nid_tra, "psrf4", itau_w, zx_tmp_2d, &  
            iim*(jjm+1), ndex2d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pplay, zx_tmp_3d)  
       CALL histwrite(nid_tra, "pplay", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
   
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, t_seri, zx_tmp_3d)  
       CALL histwrite(nid_tra, "t", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pmfu, zx_tmp_3d)  
       CALL histwrite(nid_tra, "mfu", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pmfd, zx_tmp_3d)  
       CALL histwrite(nid_tra, "mfd", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pen_u, zx_tmp_3d)  
       CALL histwrite(nid_tra, "en_u", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pen_d, zx_tmp_3d)  
       CALL histwrite(nid_tra, "en_d", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pde_d, zx_tmp_3d)  
       CALL histwrite(nid_tra, "de_d", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, pde_u, zx_tmp_3d)  
       CALL histwrite(nid_tra, "de_u", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
       CALL gr_fi_ecrit(llm, klon, iim, jjm+1, coefh, zx_tmp_3d)  
       CALL histwrite(nid_tra, "coefh", itau_w, zx_tmp_3d, &  
            iim*(jjm+1)*llm, ndex3d)  
   
       ! abder  
   
       if (ok_sync) then  
          call histsync(nid_tra)  
       endif  
   
     end subroutine write_histrac  
   
   END SUBROUTINE phytrac  
   
   !*************************************************  
   
   subroutine ini_histrac(nid_tra, pdtphys, presnivs, nqmax, lessivage)  
   
     ! From phylmd/ini_histrac.h, version 1.10 2006/02/21 08:08:30  
   
     use dimens_m, only: iim, jjm, llm  
     use ioipsl, only: ymds2ju, histbeg_totreg, histvert, histdef, histend  
     use temps, only: annee_ref, day_ref, itau_phy  
     use advtrac_m, only: niadv, tnom, ttext  
     use dimphy, only: klon  
     use clesphys, only: ecrit_tra  
     use grid_change, only: gr_phy_write  
     use phyetat0_m, only: rlon, rlat  
   
     INTEGER, intent(out):: nid_tra  
     real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)  
     REAL, intent(in):: presnivs(:)  
   
     integer, intent(in):: nqmax  
     ! (nombre de traceurs auxquels on applique la physique)  
   
     logical, intent(in):: lessivage  
   
     ! Variables local to the procedure:  
   
     REAL zjulian  
     REAL zx_lat(iim, jjm+1)  
     INTEGER nhori, nvert  
     REAL zsto, zout  
     integer it, iq, iiq  
   
     !---------------------------------------------------------  
   
     CALL ymds2ju(annee_ref, month=1, day=day_ref, sec=0.0, julian=zjulian)  
     zx_lat(:, :) = gr_phy_write(rlat)  
     CALL histbeg_totreg("histrac", iim, rlon(2:iim+1), jjm+1, zx_lat(1, :), &  
          1, iim, 1, jjm+1, itau_phy, zjulian, pdtphys, nhori, nid_tra)  
     CALL histvert(nid_tra, "presnivs", "Vertical levels", "mb", llm, &  
          presnivs, nvert)  
   
     zsto = pdtphys  
     zout = pdtphys * REAL(ecrit_tra)  
   
     CALL histdef(nid_tra, "phis", "Surface geop. height", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "once",  zsto, zout)  
     CALL histdef(nid_tra, "aire", "Grid area", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "once",  zsto, zout)  
     CALL histdef(nid_tra, "zmasse", "column density of air in cell", &  
          "kg m-2", iim, jjm + 1, nhori, llm, 1, llm, nvert, 32, "ave(X)", &  
          zsto, zout)  
   
     DO it=1, nqmax  
        ! champ 2D  
        iq=it+2  
        iiq=niadv(iq)  
        CALL histdef(nid_tra, tnom(iq), ttext(iiq), "U/kga", iim, jjm+1, &  
             nhori, llm, 1, llm, nvert, 32, "ave(X)", zsto, zout)  
405         if (lessivage) THEN         if (lessivage) THEN
406            CALL histdef(nid_tra, "fl"//tnom(iq), "Flux "//ttext(iiq), &            CALL histwrite_phy("fl"//tname(it+2), flestottr(:, :, it))
                "U/m2/s", iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
                "ave(X)", zsto, zout)  
407         endif         endif
408           CALL histwrite_phy("d_tr_th_"//tname(it+2), d_tr_th(:, :, it))
409         !---Ajout Olivia         CALL histwrite_phy("d_tr_cv_"//tname(it+2), d_tr_cv(:, :, it))
410         CALL histdef(nid_tra, "d_tr_th_"//tnom(iq), &         CALL histwrite_phy("d_tr_cl_"//tname(it+2), d_tr_cl(:, :, it))
             "tendance thermique"// ttext(iiq), "?", &  
             iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
             "ave(X)", zsto, zout)  
        CALL histdef(nid_tra, "d_tr_cv_"//tnom(iq), &  
             "tendance convection"// ttext(iiq), "?", &  
             iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
             "ave(X)", zsto, zout)  
        CALL histdef(nid_tra, "d_tr_cl_"//tnom(iq), &  
             "tendance couche limite"// ttext(iiq), "?", &  
             iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
             "ave(X)", zsto, zout)  
        !---fin Olivia      
   
411      ENDDO      ENDDO
412    
413      CALL histdef(nid_tra, "pyu1", "Vent niv 1", "-", &      if (lafin) then
414           iim, jjm+1, nhori, 1, 1, 1, -99, 32, &         call nf95_inq_varid(ncid_restartphy, "trs", varid)
415           "inst(X)", zout, zout)         call nf95_put_var(ncid_restartphy, varid, trs(:, 1))
416        endif
     CALL histdef(nid_tra, "pyv1", "Vent niv 1", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "psrf1", "nature sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "psrf2", "nature sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "psrf3", "nature sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "psrf4", "nature sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "ftsol1", "temper sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "ftsol2", "temper sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "ftsol3", "temper sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "ftsol4", "temper sol", "-", &  
          iim, jjm+1, nhori, 1, 1, 1, -99, 32, &  
          "inst(X)",  zout, zout)  
     CALL histdef(nid_tra, "pplay", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "inst(X)", zout, zout)  
     CALL histdef(nid_tra, "t", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "inst(X)", zout, zout)  
     CALL histdef(nid_tra, "mfu", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "mfd", "flux u decen", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "en_u", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "en_d", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "de_d", "flux u mont", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "de_u", "flux u decen", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
     CALL histdef(nid_tra, "coefh", "turbulent coef", "-", &  
          iim, jjm+1, nhori, llm, 1, llm, nvert, 32, &  
          "ave(X)", zsto, zout)  
   
     CALL histend(nid_tra)  
   
   end subroutine ini_histrac  
   
   !*************************************************  
   
   function radiornpb(tr_seri, pdtphys, tautr)  
   
     ! From phylmd/radiornpb.F, v 1.2 2005/05/25 13:10:09  
   
     ! Auteurs: AA + CG (LGGE/CNRS) Date 24-06-94  
     ! Objet: Decroissance radioactive d'un traceur dans l'atmosphere  
     !G 24 06 94 : Pour un traceur, le radon  
     !G 16 12 94 : Plus un 2eme traceur, le 210Pb. Le radon decroit en plomb.  
   
     ! Le pas de temps "pdtphys" est supposé beaucoup plus petit que la  
     ! constante de temps de décroissance.  
   
     use dimens_m, only: llm  
     use dimphy, only: klon, nbtr  
     use nrutil, only: assert  
   
     IMPLICIT none  
   
     REAL, intent(in):: tr_seri(:, :, :), pdtphys, tautr(:)  
     real radiornpb(klon, llm, 2)  
   
     ! Variable local to the procedure:  
     INTEGER it  
   
     !-----------------------------------------------  
   
     call assert(shape(tr_seri) == (/klon, llm, nbtr/), "radiornpb tr_seri")  
     call assert(size(tautr) == nbtr, "radiornpb tautr")  
   
     DO it = 1, 2  
        IF (tautr(it) > 0.) THEN  
           radiornpb(:, :, it) = - tr_seri(:, :, it) * pdtphys / tautr(it)  
        ELSE  
           radiornpb(:, :, it) = 0.  
        END IF  
     END DO  
   
     !G161294 : Cas particulier radon 1 => plomb 2  
     radiornpb(:, :, 2) = radiornpb(:, :, 2) - radiornpb(:, :, 1)  
   
   END function radiornpb  
   
   !*************************************************  
   
   SUBROUTINE minmaxqfi(zq, qmin, qmax, comment)  
   
     ! From phylmd/minmaxqfi.F, version 1.1.1.1 2004/05/19 12:53:09  
   
     use dimens_m, only: llm  
     use dimphy, only: klon  
     use nrutil, only: assert  
   
     IMPLICIT none  
   
     real, intent(in):: zq(:, :), qmin, qmax  
     CHARACTER(len=*), intent(in):: comment  
   
     ! Variables local to the procedure:  
   
     INTEGER jadrs(klon), jbad, k, i  
   
     !---------------------------------  
   
     call assert(shape(zq) == (/klon, llm/), "minmaxqfi")  
   
     DO k = 1, llm  
        jbad = 0  
        DO i = 1, klon  
           IF (zq(i, k) > qmax .OR. zq(i, k) < qmin) THEN  
              jbad = jbad + 1  
              jadrs(jbad) = i  
           ENDIF  
        ENDDO  
        IF (jbad > 0) THEN  
           PRINT *, comment  
           DO i = 1, jbad  
              PRINT *, "zq(", jadrs(i), ", ", k, ") = ", zq(jadrs(i), k)  
           ENDDO  
        ENDIF  
     ENDDO  
417    
418    end SUBROUTINE minmaxqfi    END SUBROUTINE phytrac
419    
420  end module phytrac_m  end module phytrac_m

Legend:
Removed from v.7  
changed lines
  Added in v.201

  ViewVC Help
Powered by ViewVC 1.1.21