Changeset 2188 for trunk/LMDZ.VENUS


Ignore:
Timestamp:
Dec 11, 2019, 5:09:28 PM (5 years ago)
Author:
flefevre
Message:
  • nouvelle version de la photochimie venusienne (calquee sur la version martienne) operationnelle
  • nettoyage de la subroutine d'interface phytrac_chimie.F
Location:
trunk/LMDZ.VENUS/libf/phyvenus
Files:
1 deleted
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.VENUS/libf/phyvenus/photochemistry_venus.F90

    r2187 r2188  
    1 subroutine photochemistry_venus(nz, n_lon, ptimestep, p, t, tr, mumean, sza_input, nesp)
     1subroutine photochemistry_venus(nz, n_lon, ptimestep, p, t, tr, mumean, sza_input, nesp, iter)
    22
    33use chemparam_mod
  • trunk/LMDZ.VENUS/libf/phyvenus/phytrac_chimie.F

    r2048 r2188  
    1 !
    2 ! $Header: /home/cvsroot/LMDZ4/libf/phylmd/phytrac.F,v 1.16 2006/03/24 15:06:23 lmdzadmin Exp $
    3 !
    4 c
    5 c
    6       SUBROUTINE  phytrac_chimie (
    7      I                    debutphy,
    8      I                    gmtime,
    9      I                    nqmax,
    10      I                    n_lon,
    11      I                    lat,
    12      I                    lon,
    13      I                    n_lev,
    14      I                    pdtphys,
    15      I                    temp,
    16      I                    pplay,
    17      O                    trac)
    18 c======================================================================
    19 c Auteur(s) FH
    20 c Objet: Moniteur general des tendances traceurs
    21 c
    22 cAA Remarques en vrac:
    23 cAA--------------------
    24 cAA 1/ le call phytrac se fait avec nqmax
    25 c======================================================================
    26       USE chemparam_mod
     1      subroutine phytrac_chimie (
     2     $                    debutphy,
     3     $                    gmtime,
     4     $                    nqmax,
     5     $                    n_lon,
     6     $                    lat,
     7     $                    lon,
     8     $                    n_lev,
     9     $                    pdtphys,
     10     $                    temp,
     11     $                    pplay,
     12     $                    trac)
     13
     14!    $                    iter) temporary
     15
     16      use chemparam_mod
    2717      use conc, only: mmean
    28       IMPLICIT none
     18
     19      implicit none
    2920     
    3021#include "clesphys.h"
    3122#include "YOMCST.h"
    32 c======================================================================
    33 c Arguments:
    34 c
    35 c
    36 c   EN ENTREE:
    37 c   ==========
    38 c
    39 c   divers:
    40 c   -------
    41 c
    42 
    43       REAL  sza_local
    44       REAL  gmtime
    45 c      INTEGER, SAVE :: cpt_cloudIO  !un compteur pour fichier sortie cloud_parameter en 1D
    46       INTEGER  iq
    47       INTEGER  i
    48       INTEGER  ilon, ilev
    49       integer  n_lon  ! nombre de points horizontaux
    50       INTEGER  n_lev  ! nombre de couches verticales
    51       INTEGER  nqmax ! nombre de traceurs auxquels on applique la physique
    52 
    53       real  pdtphys  ! pas d'integration pour la physique (seconde)
     23
     24!===================================================================
     25!     input
     26!===================================================================
     27
     28      integer :: n_lon, n_lev               ! number of gridpoints and levels
     29      integer :: nqmax                      ! number of tracers
     30
     31      real :: gmtime
     32      real :: pdtphys                       ! physics timestep (s)
     33      real, dimension(n_lon,n_lev) :: temp  ! temperature (k)
     34      real, dimension(n_lon,n_lev) :: pplay ! pressure (pa)
     35
     36      logical :: debutphy                   ! first call flag
     37
     38!===================================================================
     39!     output
     40!===================================================================
     41
     42      integer, dimension(n_lon,n_lev) :: iter ! chemical iterations
     43
     44!===================================================================
     45!     input/output
     46!===================================================================
     47
     48      real, dimension(n_lon,n_lev,nqmax) :: trac ! tracer mass mixing ratio
     49
     50!===================================================================
     51!     local
     52!===================================================================
     53
     54      real :: sza_local   ! solar zenith angle (deg)
     55      real :: lon_sun
     56
     57      integer :: i, iq
     58      integer :: ilon, ilev
     59
    5460      real  lat(n_lon), lat_local(n_lon)
    5561      real  lon(n_lon), lon_local(n_lon)
    56       real  temp(n_lon,n_lev) ! temp
    57       real  trac(n_lon,n_lev,nqmax) ! traceur
    58       real  trac_sav(n_lon,n_lev,nqmax)
    59       real  trac_sum(n_lon,n_lev)
    60       real  pplay(n_lon,n_lev)  ! pression pour le mileu de chaque couche (en Pa)
    61       real  lon_sun
    62 
    63       logical debutphy       ! le flag de l'initialisation de la physique
    64 
    65 C     Auxilary variables:
     62
     63      real, dimension(n_lon,n_lev) :: mrtwv, mrtsa ! total water and total sulfuric acid
     64      real, dimension(n_lon,n_lev) :: mrwv, mrsa   ! gas-phase water and gas-phase sulfuric acid
     65      real, dimension(n_lon,n_lev) :: trac_sum
     66     
     67!===================================================================
     68!     first call : initialisations
     69!===================================================================
     70
     71      if (debutphy) then
     72     
     73!-------------------------------------------------------------------
     74!        case of tracers re-initialisation with chemistry
     75!-------------------------------------------------------------------
     76         if (reinit_trac .and. ok_chem) then
     77
     78            print*, "Tracers are re-initialised"
     79            trac(:,:,:) = 1.0e-30
     80
     81            if ((i_ocs /= 0) .and. (i_co /= 0) .and. (i_hcl /= 0)
     82     $           .and. (i_so2 /= 0) .and. (i_h2o /= 0) .and. (i_n2/ = 0)
     83     $           .and. (i_co2 /= 0)) then
     84
     85               trac(:,1:22,i_ocs) = 3.e-6
     86               trac(:,1:22,i_co)  = 25.e-6
     87               trac(:,:,i_hcl)    = 0.4e-6
     88               trac(:,1:22,i_so2) = 10.e-6
     89               trac(:,1:22,i_h2o) = 30.e-6
     90               trac(:,:,i_n2)     = 0.35e-1
     91   
     92!          ensure that sum of mixing ratios = 1
     93
     94               trac_sum(:,:) = 0.
     95
     96               do iq = 1,nqmax - nmicro
     97                  if (iq /= i_co2) then
     98                     trac_sum(:,:) = trac_sum(:,:) + trac(:,:,iq)
     99                  end if
     100               end do
     101
     102!          initialise co2
     103
     104               trac(:,:,i_co2) = 1. - trac_sum(:,:)
     105
     106            else
     107               write(*,*) "at least one tracer is missing : stop"
     108               stop
     109            end if
     110       
     111!           convert volume to mass mixing ratio
     112
     113            do iq = 1,nqmax - nmicro
     114               trac(:,:,iq) = trac(:,:,iq)*m_tr(iq)/mmean(:,:)
     115            end do
     116   
     117         end if  ! reinit_trac
     118
     119!-------------------------------------------------------------------
     120!        case of detailed microphysics without chemistry
     121!-------------------------------------------------------------------
     122         if (.not. ok_chem .and. ok_cloud .and. cl_scheme==2) then
     123
     124!           convert mass to volume mixing ratio
     125
     126            do iq = 1,nqmax - nmicro
     127               trac(:,:,iq) = trac(:,:,iq)*mmean(:,:)/m_tr(iq)
     128            end do
     129         
     130!           initialise microphysics
    66131 
    67       REAL, DIMENSION(n_lon,n_lev) :: mrtwv,mrtsa,
    68      +                                mrwv,mrsa
     132            call vapors4muphy_ini(n_lon,n_lev,trac)
     133
     134!           convert volume to mass mixing ratio
     135
     136            do iq = 1,nqmax - nmicro
     137               trac(:,:,iq) = trac(:,:,iq)*m_tr(iq)/mmean(:,:)
     138            end do
     139   
     140         end if
     141
     142      end if  ! debutphy
     143
     144!===================================================================
     145!     convert mass to volume mixing ratio : gas phase
     146!===================================================================
     147
     148      do iq = 1,nqmax - nmicro
     149        trac(:,:,iq) = max(trac(:,:,iq)*mmean(:,:)/m_tr(iq),1.e-30)
     150      end do
     151
     152!===================================================================
     153!     microphysics: simplified scheme (phd aurelien stolzenbach)
     154!===================================================================
     155
     156      if (ok_cloud .and. cl_scheme == 1) then
     157
     158!     convert mass to volume mixing ratio : liquid phase
     159
     160         trac(:,:,i_h2so4liq) = max(trac(:,:,i_h2so4liq)
     161     $                              *mmean(:,:)/m_tr(i_h2so4liq),1.e-30)
     162         trac(:,:,i_h2oliq) = max(trac(:,:,i_h2oliq)
     163     $                            *mmean(:,:)/m_tr(i_h2oliq),1.e-30)
     164             
     165!     total water and sulfuric acid (gas + liquid)
     166
     167         mrtwv(:,:) = trac(:,:,i_h2o) + trac(:,:,i_h2oliq)
     168         mrtsa(:,:) = trac(:,:,i_h2so4) + trac(:,:,i_h2so4liq)
     169
     170!     all water and sulfuric acid is put in the gas-phase
     171
     172         mrwv(:,:) = mrtwv(:,:)
     173         mrsa(:,:) = mrtsa(:,:)
     174
     175!     call microphysics
     176
     177         call new_cloud_venus(n_lev, n_lon, temp, pplay,
     178     $                        mrtwv, mrtsa, mrwv, mrsa)
     179
     180!     update water vapour and sulfuric acid
     181
     182         trac(:,:,i_h2o) = mrwv(:,:)
     183         trac(:,:,i_h2oliq) = mrtwv(:,:) - trac(:,:,i_h2o)
    69184     
    70 C    ps_sa: satur pressure pure SA
    71 C    satps_sa: satur pres over mixture in dyne/cm2=Pa/10
    72 C----------------------------------------------------------------------------
    73        
    74 C Variables liees a l'ecriture de la bande histoire : phytrac.nc
    75  
    76       logical ok_sync
    77       parameter (ok_sync = .true.)
    78 
    79 c      modname = 'phytrac'
    80 
    81 c      PRINT*,'DEBUT subroutine PHYTRAC'
    82 
    83 c----------------------------------
    84 c debutphy: Initiation des traceurs
    85 c----------------------------------
    86 
    87       if (debutphy) then
    88      
    89          if (n_lon .EQ. 1) then           
    90          PRINT*,'n_lon 1D: ',n_lon
    91          end if
    92 
    93 c=============================================================
    94 c == CASE INIT PHOTOCHEM ==
    95 c=============================================================
    96                              
    97        IF (reinit_trac.and.ok_chem) THEN
    98        PRINT*,'REINIT MIXING RATIO TRACEURS'
    99 
    100 c                                       Passage de Rm a Rv
    101 c       =============================================================
    102 c       Necessaire si on reprend les start.nc qui sont en MMR
    103 c SEULEMENT LES GAZ
    104          DO iq=1,nqmax-nmicro
    105           trac(:,:,iq)=trac(:,:,iq)*mmean(:,:)/M_tr(iq)
    106          END DO
    107 c       =============================================================
    108          
    109 c               Initialisation des profils traceurs en Rv
    110 c=============================================================
    111 c initialisation sert a mettre les valeurs voulues par utilisateur pour
    112 c chaque traceur
    113 c exemple: trac(ilon,ilev,q)=xx
    114 
    115 c     trac_sav sert a sauver les valeurs initiales du start.nc     
    116       trac_sav=trac
    117 
    118 c     On initialise les traceurs a zero obligatoire pour la chimie
    119       trac(:,:,:)=1.0E-30
    120 
    121 c     !!! Verif traceurs !!!
    122       if (   (i_ocs.ne.0).and.(i_co.ne.0).and.(i_hcl.ne.0)
    123      &  .and.(i_so2.ne.0).and.(i_h2o.ne.0).and.(i_n2.ne.0)
    124      &  .and.(i_co2.ne.0) ) then
    125        trac(:,1:22,i_ocs)=3.E-6
    126        trac(:,1:22,i_co)=25.E-6
    127        trac(:,:,i_hcl)=0.4E-6
    128        trac(:,1:22,i_so2)=10.E-6
    129        trac(:,1:22,i_h2o)=30.0E-6
    130 
    131 c     remettre tous les traceurs du start => trac(:,:,:)=trac_sav(:,:,:)
    132 
    133 c     N2 n est pas encore une espece chimique du modele chimique
    134 c     traceur passif pour la chimie-transport
    135        trac(:,:,i_n2)=0.35d-1
    136    
    137 !!!! GG:   Initialization CO2 = 1 - qtot
    138 !!    It assures that vmr_tot = 1
    139 c     On a donc le CO2 qui est le restant d atmosphere Venus 
    140         trac_sum(:,:)=0.0
    141 c SEULEMENT LES GAZ
    142         DO iq=1,nqmax-nmicro
    143          if (iq.ne.i_co2) trac_sum(:,:)= trac_sum(:,:) + trac(:,:,iq)
    144         END DO
    145 
    146         trac(:,:,i_co2)= 1-trac_sum(:,:)
    147 
    148       else
    149         write(*,*) "Réinitialisation des traceurs avec chimie "
    150         write(*,*) "IL manque un traceur pour les options choisies"
    151         stop
    152       endif ! verif traceurs
    153        
    154 c=============================================================
    155      
    156 c                                       Passage de Rv a Rm
    157 c       =============================================================
    158 c SEULEMENT LES GAZ
    159          DO iq=1,nqmax-nmicro
    160           trac(:,:,iq)=trac(:,:,iq)*M_tr(iq)/mmean(:,:)
    161          END DO
    162 c       =============================================================
    163    
    164        ENDIF  !FIN REINIT TRAC
    165 
    166 c=============================================================
    167 c == CASE INIT GAZ when muphy without chemistry ==
    168 c=============================================================
    169                              
    170        if (.not.ok_chem.and.ok_cloud.and.(cl_scheme.eq.2)) then
    171 
    172 c                                       Passage de Rm a Rv
    173 c       =============================================================
    174 c       Necessaire si on reprend les start.nc qui sont en MMR
    175 c SEULEMENT LES GAZ
    176          DO iq=1,nqmax-nmicro
    177           trac(:,:,iq)=trac(:,:,iq)*mmean(:,:)/M_tr(iq)
    178          END DO
    179 c       =============================================================
    180          
    181         call vapors4muphy_ini(n_lon,n_lev,trac)
    182 
    183 c                                       Passage de Rv a Rm
    184 c       =============================================================
    185 c SEULEMENT LES GAZ
    186          DO iq=1,nqmax-nmicro
    187           trac(:,:,iq)=trac(:,:,iq)*M_tr(iq)/mmean(:,:)
    188          END DO
    189 c       =============================================================
    190    
    191       endif
    192        
    193 c-------------
    194 c fin debutphy
    195 c-------------
    196 
    197       ENDIF  ! fin debutphy
    198 
    199 c       =============================================================
    200 c                                       Passage de Rm a Rv
    201 c                                        DES GAZ
    202 c       =============================================================
    203       DO iq=1,nqmax-nmicro
    204         trac(:,:,iq)=MAX(trac(:,:,iq)*mmean(:,:)/M_tr(iq),1.E-30)
    205       END DO
    206 c       =============================================================
    207 
    208 
    209 c       =============================================================
    210 c           Appel Microphysique (schema simple, these Aurelien Stolzenbach)
    211 c       =============================================================
    212 
    213       IF (ok_cloud .AND. cl_scheme.eq.1) THEN
    214 
    215 c         Passage de Rm a Rv pour les liq
    216          trac(:,:,i_h2so4liq)=MAX(trac(:,:,i_h2so4liq)
    217      &                          *mmean(:,:)/M_tr(i_h2so4liq),1.E-30)
    218          trac(:,:,i_h2oliq)=MAX(trac(:,:,i_h2oliq)
    219      &                          *mmean(:,:)/M_tr(i_h2oliq),1.E-30)
    220              
    221 c      PRINT*,'DEBUT CLOUD'     
    222 c     On remet tout le RM liq dans la partie gaz
    223 c     !!! On reforme un nuage a chaque fois !!!
    224 
    225       DO ilev=1, n_lev
    226       DO ilon=1, n_lon         
    227       mrtwv(ilon,ilev)=trac(ilon,ilev,i_h2o) +
    228      &  trac(ilon,ilev,i_h2oliq)
    229       mrtsa(ilon,ilev)=trac(ilon,ilev,i_h2so4) +
    230      &  trac(ilon,ilev,i_h2so4liq)
    231       mrwv(ilon,ilev)=mrtwv(ilon,ilev)
    232       mrsa(ilon,ilev)=mrtsa(ilon,ilev)
    233       ENDDO
    234       ENDDO
    235                    
    236       CALL new_cloud_venus(n_lev, n_lon,
    237      e temp,pplay,
    238      e mrtwv,mrtsa,
    239      e mrwv,mrsa)
    240 
    241 c       =========================================               
    242 c       Actualisation des mixing ratio liq et gaz
    243 c       =========================================
    244 c       Si la routine new_cloud_venus n'a pas actualise mrwv et mrsa
    245 c       on a alors bien mr=mrt pour sa et wv, donc les parties liq sont=0 hors du nuage
    246 c       ou si on ne condense pas
    247 
    248 c      PRINT*,'DEBUT ACTUALISATION OUTPUT CLOUD'
    249 c    si tout se passe bien, mrtwv et mrtsa ne changent pas
    250       DO ilev=1, n_lev
    251       DO ilon=1, n_lon       
    252       trac(ilon,ilev,i_h2o) = mrwv(ilon,ilev)
    253       trac(ilon,ilev,i_h2oliq) = mrtwv(ilon,ilev) -
    254      &  trac(ilon,ilev,i_h2o)
    255      
    256       trac(ilon,ilev,i_h2so4) = mrsa(ilon,ilev)
    257       trac(ilon,ilev,i_h2so4liq) = mrtsa(ilon,ilev) -
    258      &  trac(ilon,ilev,i_h2so4)
    259       ENDDO
    260       ENDDO
    261 
    262 c       =============================================================
    263 c      PRINT*,'FIN CLOUD, scheme 1'
    264       ENDIF 
    265 
    266 c       =============================================================
    267 c           Appel Microphysique (schema complet, these Sabrina Guilbon)
    268 c       =============================================================
    269 
    270       IF (ok_cloud .AND. cl_scheme.eq.2) THEN
     185         trac(:,:,i_h2so4) = mrsa(:,:)
     186         trac(:,:,i_h2so4liq) = mrtsa(:,:) - trac(:,:,i_h2so4)
     187
     188      end if  ! simplified scheme
     189
     190!===================================================================
     191!     microphysics: detailed scheme (phd sabrina guilbon)
     192!===================================================================
     193
     194      if (ok_cloud .and. cl_scheme == 2) then
    271195
    272196c       Boucle sur grille (n_lon) et niveaux (n_lev)
     
    302226        ENDDO
    303227
    304 
    305 c       =============================================================
    306 c      PRINT*,'FIN CLOUD, scheme 2'
    307       ENDIF 
    308 
     228      end if  ! detailed scheme
    309229           
    310 c=============================================================
    311 c               CHIMIE: Boucle sur les lon, lat (n_lon)
    312 c=============================================================
    313 
    314 c     AS:
    315 c     Ici, la longitude au midi local se deplace vers l'Ouest
    316 c     c'est le sens terrestre
    317 c     pour Venus on prend juste l'oppose de la longitude et on a la rotation
    318 c     de Venus et donc le midi local qui se deplace vers l'Est
    319      
    320       lon_sun = (0.5 - gmtime) * 2.0 * RPI
    321       lon_local = lon * RPI/180.0E+0
    322       lat_local = lat * RPI/180.0E+0
    323        
    324       IF (ok_chem) THEN
    325 
    326 c      PRINT*,'DEBUT CHEMISTRY'
    327       DO ilon=1, n_lon
    328 
    329 c     calcul sza_local pour obtenir des sza_local > 90, utile pour la chimie
    330       sza_local = acos(cos(lat_local(ilon))*cos(lon_local(ilon))*
    331      & cos(lon_sun) + cos(lat_local(ilon))*sin(lon_local(ilon))
    332      & *sin(lon_sun))* 180.0E+0/RPI
    333      
    334 c      PRINT*,'sza_local :', sza_local     
    335    
    336 c       =============================================================
    337 c                                       Appel Photochimie
    338 c       =============================================================
    339 c     Pression en hPa => pplay/100.
    340        
    341       CALL new_photochemistry_venus(n_lev, n_lon, pdtphys,
    342      e                         pplay(ilon,:)/100.,
    343      e                         temp(ilon,:),
    344      e                         trac(ilon,:,:),
    345      e                         mmean(ilon,:),
    346      e                         sza_local, nqmax)
    347 c       =============================================================
    348 
    349       END DO
    350 c      PRINT*,'FIN CHEMISTRY'
    351    
    352       END IF
    353 c=============================================================
    354 
    355 c       =============================================================
    356 c                                       Passage de Rv a Rm
    357 c       =============================================================
    358 c                                        DES GAZ
    359       DO iq=1,nqmax-nmicro
    360                 trac(:,:,iq)=trac(:,:,iq)*M_tr(iq)/mmean(:,:)
    361 
    362       END DO
    363 
    364       IF (ok_cloud .AND. cl_scheme.eq.1) THEN
    365 c         Passage de Rv a Rm pour les liq
    366          trac(:,:,i_h2so4liq)=trac(:,:,i_h2so4liq)*M_tr(i_h2so4liq)
     230!===================================================================
     231!     photochemistry
     232!===================================================================
     233
     234      if (ok_chem) then
     235
     236         lon_sun = (0.5 - gmtime)*2.*rpi
     237         lon_local(:) = lon(:)*rpi/180.
     238         lat_local(:) = lat(:)*rpi/180.
     239
     240         do ilon = 1,n_lon
     241
     242!           solar zenith angle
     243
     244            sza_local = acos(cos(lat_local(ilon))*cos(lon_local(ilon))
     245     $                 *cos(lon_sun) + cos(lat_local(ilon))
     246     $                 *sin(lon_local(ilon))*sin(lon_sun))*180./rpi
     247     
     248            call photochemistry_venus(n_lev, n_lon, pdtphys,
     249     $                                pplay(ilon,:)/100.,
     250     $                                temp(ilon,:),
     251     $                                trac(ilon,:,:),
     252     $                                mmean(ilon,:),
     253     $                                sza_local, nqmax, iter(ilon,:))
     254
     255         end do
     256
     257      end if  ! ok_chem
     258
     259!===================================================================
     260!     convert volume to mass mixing ratio
     261!===================================================================
     262
     263!     gas phase
     264
     265      do iq = 1,nqmax - nmicro
     266         trac(:,:,iq) = trac(:,:,iq)*m_tr(iq)/mmean(:,:)
     267      end do
     268
     269!     liquid phase
     270
     271      if (ok_cloud .and. cl_scheme == 1) then
     272         trac(:,:,i_h2so4liq) = trac(:,:,i_h2so4liq)*m_tr(i_h2so4liq)
    367273     &                          /mmean(:,:)
    368          trac(:,:,i_h2oliq)=trac(:,:,i_h2oliq)*M_tr(i_h2oliq)
    369      &                          /mmean(:,:)
    370       ENDIF
    371      
    372 c       =============================================================   
    373 C      PRINT*,'FIN PHYTRAC'
    374       RETURN
    375       END
     274         trac(:,:,i_h2oliq) = trac(:,:,i_h2oliq)*m_tr(i_h2oliq)
     275     &                        /mmean(:,:)
     276      end if
     277     
     278      end subroutine phytrac_chimie
Note: See TracChangeset for help on using the changeset viewer.