Changeset 2030 for trunk


Ignore:
Timestamp:
Oct 28, 2018, 5:55:23 PM (6 years ago)
Author:
flefevre
Message:

photolyse on-line:

  • regroupement des parametres en module
  • suppression des appels a chimiedata.h inutiles
  • optimisation geometrie spherique
  • revision des intervalles spectraux
Location:
trunk/LMDZ.MARS/libf/aeronomars
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/aeronomars/calchim.F90

    r2029 r2030  
    6868!=======================================================================
    6969
    70 #include "chimiedata.h"
    7170#include "callkeys.h"
    7271
     
    152151      real    :: zv(ngrid,nlayer)      ! v component of the wind
    153152      real    :: taucol                ! dust optical depth at the surface
     153      real    :: kb                    ! boltzmann constant
    154154
    155155      logical,save :: firstcall = .true.
     
    168168      real :: surfdust1d(nlayer)   ! Dust surface area (cm2/cm3)
    169169      real :: jo3(nlayer)          ! Photodissociation rate O3->O1D (s-1)
     170      real :: jh2o(nlayer)         ! Photodissociation rate H2O->H+OH (s-1)
    170171      real :: em_no(nlayer)        !  NO nightglow emission rate
    171172      real :: em_o2(nlayer)        !  O2 nightglow emission rate     
     
    179180      parameter (output = .true.)
    180181      real :: jo3_3d(ngrid,nlayer)  ! Photodissociation rate O3->O1D (s-1)
     182      real :: jh2o_3d(ngrid,nlayer)  ! Photodissociation rate H2O->H+OH (s-1)
    181183      real :: emission_no(ngrid,nlayer) !NO emission rate
    182184      real :: emission_o2(ngrid,nlayer) !O2 emission rate
     
    600602      dqchim(:,:,:) = 0.
    601603      dqschim(:,:)  = 0.
     604
     605      kb = 1.3806e-23
    602606
    603607!     latvl1= 22.27
     
    664668                           ig,lswitch,zycol,szacol,ptimestep,         &
    665669                           zpress,zlocal,ztemp,zdens,zmmean,dist_sol, &
    666                            surfdust1d,surfice1d,jo3,taucol,iter)
     670                           surfdust1d,surfice1d,jo3,jh2o,taucol,iter)
    667671
    668672!        ozone photolysis, for output
     
    670674            do l = 1,nlayer
    671675               jo3_3d(ig,l) = jo3(l)
     676               jh2o_3d(ig,l) = jh2o(l)
    672677               iter_3d(ig,l) = iter(l)
    673678            end do
     
    741746            call writediagfi(ngrid,'jo3','j o3->o1d',    &
    742747                             's-1',3,jo3_3d(1,1))
     748            call writediagfi(ngrid,'jh2o','jh2o',    &
     749                             's-1',3,jh2o_3d(1,1))
    743750            call writediagfi(ngrid,'iter','iterations',  &
    744751                             ' ',3,iter_3d(1,1))
  • trunk/LMDZ.MARS/libf/aeronomars/chimiedata.h

    r2024 r2030  
    3333
    3434      data tautab/0., 0.2, 0.4, 0.6, 0.8, 1., 2., 4./
    35 
    36 !--------------------------------------------
    37 !     number of reactions in ASIS solver
    38 !--------------------------------------------
    39 
    40       integer, parameter :: nb_phot_max       = 22
    41       integer, parameter :: nb_reaction_3_max = 6
    42       integer, parameter :: nb_reaction_4_max = 31
  • trunk/LMDZ.MARS/libf/aeronomars/concentrations.F

    r1660 r2030  
    2828 
    2929#include "callkeys.h"
    30 #include "chimiedata.h"
    3130
    3231!     input/output
  • trunk/LMDZ.MARS/libf/aeronomars/moldiffcoeff.F

    r1266 r2030  
    1717c=======================================================================
    1818#include "callkeys.h"
    19 #include "chimiedata.h"
    2019
    2120c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/aeronomars/moldiffcoeff_red.F

    r1266 r2030  
    1313c=======================================================================
    1414#include "callkeys.h"
    15 #include "chimiedata.h"
    1615#include "diffusion.h"
    1716
  • trunk/LMDZ.MARS/libf/aeronomars/photochemistry.F90

    r2029 r2030  
    1616                          ig, lswitch, zycol, sza, ptimestep, press,    &
    1717                          alt, temp, dens, zmmean, dist_sol, surfdust1d,&
    18                           surfice1d, jo3, tau, iter)
    19 
     18                          surfice1d, jo3, jh2o, tau, iter)
     19
     20use photolysis_mod, only : nb_phot_max,       &
     21                           nb_reaction_3_max, &
     22                           nb_reaction_4_max
    2023implicit none
    2124
    22 #include "chimiedata.h"
    2325#include "callkeys.h"
    2426
     
    5557integer :: iter(nlayer)        ! iteration counter
    5658real    :: jo3(nlayer)         ! photodissociation rate o3 -> o1d
     59real    :: jh2o(nlayer)        ! photodissociation rate h2o -> h + oh
    5760
    5861!===================================================================
     
    6366
    6467integer :: phychemrat            ! (physical timestep)/(nominal chemical timestep)
    65 integer :: j_o3_o1d, ilev, iesp
     68integer :: j_o3_o1d, j_h2o, ilev, iesp
    6669integer :: lswitch
    6770logical, save :: firstcall = .true.
    68 logical :: jonline
     71logical :: jonline               ! switch for online photolysis
    6972
    7073! tracer indexes in the chemistry:
     
    140143!===================================================================
    141144
    142 jonline = .false.  ! .false. recommended until the end of testing phase
     145jonline = .false.
    143146
    144147if (jonline) then
    145    if (sza <= 120.) then ! day
    146       tau = tau*press(1)/6.1  ! temporary
     148   if (sza <= 113.) then ! day at 300 km
     149      tau = tau*press(1)/7.  ! temporary
    147150      call photolysis_online(nlayer, alt, press, temp, zmmean,          &
    148151                             i_co2, i_co, i_o, i_o1d, i_o2, i_o3, i_h,  &
     
    158161end if
    159162
    160 ! save o3 photolysis for output
     163! save o3 and h2o photolysis for output
    161164
    162165j_o3_o1d = 5
    163166jo3(:) = v_phot(:,j_o3_o1d)
     167j_h2o = 7
     168jh2o(:) = v_phot(:,j_h2o)
    164169
    165170!===================================================================
     
    418423
    419424use comcstfi_h
     425use photolysis_mod, only : nphot, nb_phot_max, &
     426                           nb_reaction_3_max,  &
     427                           nb_reaction_4_max
    420428
    421429implicit none
    422 
    423 #include "chimiedata.h"
    424430
    425431!----------------------------------------------------------------------
     
    473479!----------------------------------------------------------------------
    474480
    475       nb_phot       = 13       ! jmars.20140930(13) - hno3 - hno4 + h2 + n2
     481      nb_phot       = nphot ! initialised to the number of photolysis rates
    476482      nb_reaction_3 = 0
    477483      nb_reaction_4 = 0
     
    10441050
    10451051use types_asis
     1052use photolysis_mod, only : nb_phot_max,       &
     1053                           nb_reaction_3_max, &
     1054                           nb_reaction_4_max
    10461055
    10471056implicit none
    1048 
    1049 #include "chimiedata.h"
    10501057
    10511058! input
     
    11701177
    11711178use types_asis
     1179use photolysis_mod, only : nb_phot_max,       &
     1180                           nb_reaction_3_max, &
     1181                           nb_reaction_4_max
    11721182
    11731183implicit none
    1174 
    1175 #include "chimiedata.h"
    11761184
    11771185! input
  • trunk/LMDZ.MARS/libf/aeronomars/photolysis.F90

    r2024 r2030  
    88
    99      use comcstfi_h
     10      use photolysis_mod, only : nb_phot_max
    1011
    1112      implicit none
     
    333334         v_phot(l, 8) = j(l,j_h2o2)
    334335         v_phot(l, 9) = j(l,j_ho2)
    335          v_phot(l,10) = 0.         ! h2
     336         v_phot(l,10) = 0.         ! h2 missing in lookup table
    336337         v_phot(l,11) = j(l,j_no)
    337338         v_phot(l,12) = j(l,j_no2)
    338          v_phot(l,13) = 0.         ! n2
     339         v_phot(l,13) = 0.         ! n2 missing in lookup table
    339340      end do
    340341
  • trunk/LMDZ.MARS/libf/aeronomars/photolysis_mod.F90

    r2029 r2030  
    33  implicit none
    44
     5  integer, parameter :: nphot = 13        ! number of photolysis
     6  integer, parameter :: nabs  = 10        ! number of absorbing gases
     7
     8! number of reactions in chemical solver
     9
     10  integer, parameter :: nb_phot_max       = nphot + 9 ! photolysis + quenching/heterogeneous
     11  integer, parameter :: nb_reaction_3_max = 6         ! quadratic
     12  integer, parameter :: nb_reaction_4_max = 31        ! bimolecular
     13
    514! spectral grid
    615
    7   integer, parameter :: nw = 152          ! number of spectral intervals (low-res)
     16  integer, parameter :: nw = 162          ! number of spectral intervals (low-res)
    817  integer :: mopt                         ! high-res/low-res switch
    918
     
    136145!                    0-60 nm :  6.0 nm
    137146!                   60-80 nm :  2.0 nm
    138 !                  80-120 nm :  5.0 nm
     147!                   80-85 nm :  5.0 nm
     148!                  85-117 nm :  2.0 nm
     149!                 117-120 nm :  5.0 nm
    139150!                 120-123 nm :  0.2 nm
    140151!                 123-163 nm :  5.0 nm
     
    209220      wl(kw+1) = wu(kw)
    210221
     222!============================================================
     223
    211224      else if (mopt == 2) then   ! low-res
    212225
     
    232245      END DO
    233246
    234 ! define wavelength intervals of width 5.0 nm from 80 to 120 nm:
     247! define wavelength intervals of width 5.0 nm from 80 to 85 nm:
    235248
    236249      wincr = 5.0
    237       DO iw = 80, 115, 5
     250      DO iw = 80, 80, 5
     251        kw = kw + 1
     252        wl(kw) = real(iw)
     253        wu(kw) = wl(kw) + wincr
     254        wc(kw) = (wl(kw) + wu(kw))/2.
     255      END DO
     256
     257! define wavelength intervals of width 2.0 nm from 85 to 117 nm:
     258
     259      wincr = 2.0
     260      DO iw = 85, 115, 2
     261        kw = kw + 1
     262        wl(kw) = real(iw)
     263        wu(kw) = wl(kw) + wincr
     264        wc(kw) = (wl(kw) + wu(kw))/2.
     265      END DO
     266
     267! define wavelength intervals of width 5.0 nm from 117 to 120 nm:
     268
     269      wincr = 3.0
     270      DO iw = 117, 117, 3
    238271        kw = kw + 1
    239272        wl(kw) = real(iw)
     
    250283        wu(kw) = wl(kw) + wincr
    251284        wc(kw) = (wl(kw) + wu(kw))/2.
    252       END DO
     285      ENDDO
    253286
    254287! define wavelength intervals of width 5.0 nm from 123 to 163 nm:
     
    260293        wu(kw) = wl(kw) + wincr
    261294        wc(kw) = (wl(kw) + wu(kw))/2.
    262       END DO
     295      ENDDO
    263296
    264297! define wavelength intervals of width 2.0 nm from 163 to 175 nm:
     
    270303        wu(kw) = wl(kw) + wincr
    271304        wc(kw) = (wl(kw) + wu(kw))/2.
    272       END DO
     305      ENDDO
    273306
    274307! define wavelength intervals of width 0.5 nm from 175 to 205 nm:
     
    280313        wu(kw) = wl(kw) + wincr
    281314        wc(kw) = (wl(kw) + wu(kw))/2.
    282       END DO
     315      ENDDO
    283316
    284317! define wavelength intervals of width 5.0 nm from 205 to 245 nm:
     
    290323        wu(kw) = wl(kw) + wincr
    291324        wc(kw) = (wl(kw) + wu(kw))/2.
    292       END DO
     325      ENDDO
    293326
    294327! define wavelength intervals of width 10.0 nm from 245 to 415 nm:
     
    300333        wu(kw) = wl(kw) + wincr
    301334        wc(kw) = (wl(kw) + wu(kw))/2.
    302       END DO
     335      ENDDO
    303336
    304337! define wavelength intervals of width 50.0 nm from 415 to 815 nm:
     
    310343        wu(kw) = wl(kw) + wincr
    311344        wc(kw) = (wl(kw) + wu(kw))/2.
    312       END DO
     345      ENDDO
    313346
    314347      wl(kw+1) = wu(kw)
    315348
    316349      end if  ! mopt
     350
     351      print*, 'number of spectral intervals : ', kw+1
    317352     
    318 !     do iw = 1,nw
    319 !        write(20,*) iw, wl(iw), wu(iw)
    320 !     end do
    321       print*, 'number of spectral intervals : ', kw+1
    322 
    323353      end subroutine gridw
    324354
  • trunk/LMDZ.MARS/libf/aeronomars/photolysis_online.F

    r2029 r2030  
    1010
    1111      implicit none
    12 
    13 #include "chimiedata.h"
    1412
    1513!     input
     
    3937!     cross-sections
    4038
    41       integer, parameter  :: nabs  = 10                              ! number of absorbing gases
    42       integer, parameter  :: nphot = 13                              ! number of photolysis
    4339      real, dimension(nlayer,nw,nphot) :: sj                         ! general cross-section array (cm2)
    4440
     
    920916              gb = rjp1*rjp1 - rpsinz*rpsinz
    921917
    922               IF (ga .LT. 0.0) ga = 0.0
    923               IF (gb .LT. 0.0) gb = 0.0
     918              ga = max(ga, 0.)
     919              gb = max(gb, 0.)
    924920 
    925921              IF (id.GT.i .AND. j.EQ.id) THEN
  • trunk/LMDZ.MARS/libf/aeronomars/surfacearea.F

    r1528 r2030  
    2020
    2121      include "callkeys.h"
    22       include "chimiedata.h"
    2322
    2423! input
Note: See TracChangeset for help on using the changeset viewer.