source: trunk/LMDZ.VENUS/libf/phyvenus/phytrac_chimie.F @ 2200

Last change on this file since 2200 was 2200, checked in by flefevre, 5 years ago

correction de bugs dans le supercycling de la chimie

  • Property svn:executable set to *
File size: 10.7 KB
RevLine 
[2188]1      subroutine phytrac_chimie (
2     $                    debutphy,
3     $                    gmtime,
4     $                    nqmax,
[2193]5     $                    nlon,
[2188]6     $                    lat,
7     $                    lon,
[2193]8     $                    nlev,
[2188]9     $                    pdtphys,
10     $                    temp,
11     $                    pplay,
[2193]12     $                    trac,
13     $                    d_tr_chem,
14     $                    iter)
[2188]15
16      use chemparam_mod
[1442]17      use conc, only: mmean
[2188]18
19      implicit none
[1305]20     
21#include "clesphys.h"
22#include "YOMCST.h"
23
[2188]24!===================================================================
25!     input
26!===================================================================
[1442]27
[2193]28      integer :: nlon, nlev                     ! number of gridpoints and levels
29      integer :: nqmax                          ! number of tracers
[1442]30
[2193]31      real :: gmtime                            ! day fraction
32      real :: pdtphys                           ! phytrac_chimie timestep (s)
33      real, dimension(nlon,nlev) :: temp        ! temperature (k)
34      real, dimension(nlon,nlev) :: pplay       ! pressure (pa)
35      real, dimension(nlon,nlev,nqmax) :: trac  ! tracer mass mixing ratio
[1305]36
[2193]37      logical :: debutphy                       ! first call flag
[1305]38
[2188]39!===================================================================
40!     output
41!===================================================================
[1305]42
[2193]43      real, dimension(nlon,nlev,nqmax) :: d_tr_chem  ! chemical tendency for each tracer
44      integer, dimension(nlon,nlev) :: iter          ! chemical iterations
[1305]45
[2188]46!===================================================================
47!     local
48!===================================================================
49
50      real :: sza_local   ! solar zenith angle (deg)
51      real :: lon_sun
52
53      integer :: i, iq
54      integer :: ilon, ilev
55
[2193]56      real  lat(nlon), lat_local(nlon)
57      real  lon(nlon), lon_local(nlon)
[2188]58
[2193]59      real, dimension(nlon,nlev) :: mrtwv, mrtsa ! total water and total sulfuric acid
60      real, dimension(nlon,nlev) :: mrwv, mrsa   ! gas-phase water and gas-phase sulfuric acid
61      real, dimension(nlon,nlev) :: trac_sum
62      real, dimension(nlon,nlev,nqmax) :: ztrac  ! local tracer mixing ratio
[2188]63     
64!===================================================================
65!     first call : initialisations
66!===================================================================
67
[1305]68      if (debutphy) then
69     
[2188]70!-------------------------------------------------------------------
71!        case of tracers re-initialisation with chemistry
72!-------------------------------------------------------------------
73         if (reinit_trac .and. ok_chem) then
[1661]74
[2188]75            print*, "Tracers are re-initialised"
76            trac(:,:,:) = 1.0e-30
[1305]77
[2188]78            if ((i_ocs /= 0) .and. (i_co /= 0) .and. (i_hcl /= 0)
79     $           .and. (i_so2 /= 0) .and. (i_h2o /= 0) .and. (i_n2/ = 0)
80     $           .and. (i_co2 /= 0)) then
[1305]81
[2188]82               trac(:,1:22,i_ocs) = 3.e-6
83               trac(:,1:22,i_co)  = 25.e-6
84               trac(:,:,i_hcl)    = 0.4e-6
85               trac(:,1:22,i_so2) = 10.e-6
86               trac(:,1:22,i_h2o) = 30.e-6
87               trac(:,:,i_n2)     = 0.35e-1
88   
89!          ensure that sum of mixing ratios = 1
[1305]90
[2188]91               trac_sum(:,:) = 0.
[1305]92
[2188]93               do iq = 1,nqmax - nmicro
94                  if (iq /= i_co2) then
95                     trac_sum(:,:) = trac_sum(:,:) + trac(:,:,iq)
96                  end if
97               end do
[1305]98
[2188]99!          initialise co2
[1305]100
[2188]101               trac(:,:,i_co2) = 1. - trac_sum(:,:)
[1305]102
[2188]103            else
104               write(*,*) "at least one tracer is missing : stop"
105               stop
106            end if
107       
108!           convert volume to mass mixing ratio
[2048]109
[2188]110            do iq = 1,nqmax - nmicro
111               trac(:,:,iq) = trac(:,:,iq)*m_tr(iq)/mmean(:,:)
112            end do
[1442]113   
[2188]114         end if  ! reinit_trac
[1305]115
[2188]116!-------------------------------------------------------------------
117!        case of detailed microphysics without chemistry
118!-------------------------------------------------------------------
[2193]119         if (.not. ok_chem .and. ok_cloud .and. cl_scheme == 2) then
[1661]120
[2188]121!           convert mass to volume mixing ratio
122
123            do iq = 1,nqmax - nmicro
[2193]124               ztrac(:,:,iq) = trac(:,:,iq)*mmean(:,:)/m_tr(iq)
[2188]125            end do
[1661]126         
[2188]127!           initialise microphysics
128 
[2193]129            call vapors4muphy_ini(nlon,nlev,ztrac)
[1661]130
[2188]131!           convert volume to mass mixing ratio
132
133            do iq = 1,nqmax - nmicro
[2193]134               trac(:,:,iq) = ztrac(:,:,iq)*m_tr(iq)/mmean(:,:)
[2188]135            end do
[1661]136   
[2188]137         end if
[1442]138
[2188]139      end if  ! debutphy
[1305]140
[2188]141!===================================================================
142!     convert mass to volume mixing ratio : gas phase
143!===================================================================
[1305]144
[2188]145      do iq = 1,nqmax - nmicro
[2193]146         ztrac(:,:,iq) = max(trac(:,:,iq)*mmean(:,:)/m_tr(iq), 1.e-30)
[2188]147      end do
[1305]148
[2188]149!===================================================================
150!     microphysics: simplified scheme (phd aurelien stolzenbach)
151!===================================================================
[1305]152
[2188]153      if (ok_cloud .and. cl_scheme == 1) then
[1661]154
[2188]155!     convert mass to volume mixing ratio : liquid phase
156
[2193]157         ztrac(:,:,i_h2so4liq) = max(trac(:,:,i_h2so4liq)
158     $                             *mmean(:,:)/m_tr(i_h2so4liq), 1.e-30)
159         ztrac(:,:,i_h2oliq) = max(trac(:,:,i_h2oliq)
160     $                             *mmean(:,:)/m_tr(i_h2oliq), 1.e-30)
[1661]161             
[2188]162!     total water and sulfuric acid (gas + liquid)
[1305]163
[2193]164         mrtwv(:,:) = ztrac(:,:,i_h2o) + ztrac(:,:,i_h2oliq)
165         mrtsa(:,:) = ztrac(:,:,i_h2so4) + ztrac(:,:,i_h2so4liq)
[1305]166
[2188]167!     all water and sulfuric acid is put in the gas-phase
[1305]168
[2188]169         mrwv(:,:) = mrtwv(:,:)
170         mrsa(:,:) = mrtsa(:,:)
171
172!     call microphysics
173
[2193]174         call new_cloud_venus(nlev, nlon, temp, pplay,
[2188]175     $                        mrtwv, mrtsa, mrwv, mrsa)
176
177!     update water vapour and sulfuric acid
178
[2193]179         ztrac(:,:,i_h2o) = mrwv(:,:)
180         ztrac(:,:,i_h2oliq) = mrtwv(:,:) - ztrac(:,:,i_h2o)
[1305]181     
[2193]182         ztrac(:,:,i_h2so4) = mrsa(:,:)
183         ztrac(:,:,i_h2so4liq) = mrtsa(:,:) - ztrac(:,:,i_h2so4)
[1305]184
[2188]185      end if  ! simplified scheme
[1661]186
[2188]187!===================================================================
188!     microphysics: detailed scheme (phd sabrina guilbon)
[2197]189!     !!! to be confirmed whether mad_muphy expects mmr or vmr for h2o and h2so4
[2188]190!===================================================================
[1661]191
[2188]192      if (ok_cloud .and. cl_scheme == 2) then
[1661]193
[2197]194         do iq = nqmax-nmicro+1,nqmax
195            ztrac(:,:,iq) = trac(:,:,iq)
196         end do
197
[2193]198         do ilon = 1,nlon       
199            do ilev = 1, nlev
200               if (temp(ilon,ilev) < 500.) then
201                  call mad_muphy(pdtphys,                               ! timestep
202     $                           temp(ilon,ilev),pplay(ilon,ilev),      ! temperature and pressure
203     $                           ztrac(ilon,ilev,i_h2o),
204     $                           ztrac(ilon,ilev,i_h2so4),     
205     $                           ztrac(ilon,ilev,i_m0_aer),
206     $                           ztrac(ilon,ilev,i_m3_aer),   
207     $                           ztrac(ilon,ilev,i_m0_mode1drop),
208     $                           ztrac(ilon,ilev,i_m0_mode1ccn),
209     $                           ztrac(ilon,ilev,i_m3_mode1sa),
210     $                           ztrac(ilon,ilev,i_m3_mode1w),   
211     $                           ztrac(ilon,ilev,i_m3_mode1ccn),   
212     $                           ztrac(ilon,ilev,i_m0_mode2drop),
213     $                           ztrac(ilon,ilev,i_m0_mode2ccn),
214     $                           ztrac(ilon,ilev,i_m3_mode2sa),
215     $                           ztrac(ilon,ilev,i_m3_mode2w),
216     $                           ztrac(ilon,ilev,i_m3_mode2ccn))
217               else
218                  ztrac(ilon,ilev,i_m0_aer)       = 0.
219                  ztrac(ilon,ilev,i_m3_aer)       = 0.
220                  ztrac(ilon,ilev,i_m0_mode1drop) = 0.
221                  ztrac(ilon,ilev,i_m0_mode1ccn)  = 0.
222                  ztrac(ilon,ilev,i_m3_mode1sa)   = 0.
223                  ztrac(ilon,ilev,i_m3_mode1w)    = 0.
224                  ztrac(ilon,ilev,i_m3_mode1ccn)  = 0.
225                  ztrac(ilon,ilev,i_m0_mode2drop) = 0.
226                  ztrac(ilon,ilev,i_m0_mode2ccn)  = 0.
227                  ztrac(ilon,ilev,i_m3_mode2sa)   = 0.
228                  ztrac(ilon,ilev,i_m3_mode2w)    = 0.
229                  ztrac(ilon,ilev,i_m3_mode2ccn)  = 0.
230               end if
231            end do
232         end do
[1661]233
[2188]234      end if  ! detailed scheme
235           
236!===================================================================
237!     photochemistry
238!===================================================================
[1661]239
[2188]240      if (ok_chem) then
[1661]241
[2188]242         lon_sun = (0.5 - gmtime)*2.*rpi
243         lon_local(:) = lon(:)*rpi/180.
244         lat_local(:) = lat(:)*rpi/180.
[1442]245
[2193]246         do ilon = 1,nlon
[1661]247
[2188]248!           solar zenith angle
[1442]249
[2188]250            sza_local = acos(cos(lat_local(ilon))*cos(lon_local(ilon))
251     $                 *cos(lon_sun) + cos(lat_local(ilon))
252     $                 *sin(lon_local(ilon))*sin(lon_sun))*180./rpi
[1305]253     
[2193]254            call photochemistry_venus(nlev, nlon, pdtphys,
[2188]255     $                                pplay(ilon,:)/100.,
256     $                                temp(ilon,:),
[2193]257     $                                ztrac(ilon,:,:),
[2188]258     $                                mmean(ilon,:),
259     $                                sza_local, nqmax, iter(ilon,:))
[1661]260
[2188]261         end do
[1305]262
[2188]263      end if  ! ok_chem
[1442]264
[2188]265!===================================================================
[2193]266!     compute tendencies
[2188]267!===================================================================
[1661]268
[2188]269!     gas phase
270
271      do iq = 1,nqmax - nmicro
[2200]272         ztrac(:,:,iq) = max(ztrac(:,:,iq)*m_tr(iq)/mmean(:,:),
273     $                       1.e-30)
[2193]274         d_tr_chem(:,:,iq) = (ztrac(:,:,iq) - trac(:,:,iq))/pdtphys
[2188]275      end do
276
[2194]277!     liquid phase or moments
[2188]278
279      if (ok_cloud .and. cl_scheme == 1) then
[2200]280         ztrac(:,:,i_h2so4liq) = max(ztrac(:,:,i_h2so4liq)
281     $                               *m_tr(i_h2so4liq)/mmean(:,:),
282     $                               1.e-30)
283         ztrac(:,:,i_h2oliq)   = max(ztrac(:,:,i_h2oliq)
284     $                               *m_tr(i_h2oliq)/mmean(:,:),
285     $                               1.e-30)
[2193]286         d_tr_chem(:,:,i_h2so4liq) = (ztrac(:,:,i_h2so4liq)
287     $                              - trac(:,:,i_h2so4liq))/pdtphys
288         d_tr_chem(:,:,i_h2oliq) = (ztrac(:,:,i_h2oliq)
289     $                            - trac(:,:,i_h2oliq))/pdtphys
[2188]290      end if
[2193]291
[2194]292
293      if (ok_cloud .and. cl_scheme == 2) then
294         do iq = nqmax-nmicro+1,nqmax
295            d_tr_chem(:,:,iq) = (ztrac(:,:,iq) - trac(:,:,iq))/pdtphys
296         end do
297      end if
298
[2188]299      end subroutine phytrac_chimie
Note: See TracBrowser for help on using the repository browser.