Ignore:
Timestamp:
Jan 15, 2018, 12:08:11 PM (7 years ago)
Author:
jvatant
Message:

Making chemistry more flexible - step 3.5
+ Update phyredem and phyetat0 ( with a chem_settings.F90 init routine )
+ Finish the handling of upper chem fields by their names everywhere
( with hardcoded cnames and mmol moved from tracer_h to comchem_h )
--JVO

Location:
trunk/LMDZ.TITAN/libf/phytitan
Files:
1 added
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/comchem_h.F90

    r1892 r1894  
    11MODULE comchem_h
    22
    3 ! -----------------------------------------------------------------------
    4 ! Purpose : Stores data relative to upper chemistry in the GCM
    5 ! -------   For newstart there is a specific comchem_newstart_h module.
     3! ----------------------------------------------------------------------------
     4! Purpose : Stores data relative to chemistry in the GCM and upper chemistry
     5! -------
     6!          NB : For newstart there is a specific comchem_newstart_h module.
    67!
    7 ! Author : Jan Vatant d'Ollone (2017)
     8! Author : Jan Vatant d'Ollone (2017-18)
    89! ------
    910!
     
    1415!      N4S, CN, HCN, H2CN, CHCN, CH2CN, CH3CN, C3N, HC3N, NCCN, C4N2
    1516       
    16 ! --------------------------------------------------------------------------
     17! ----------------------------------------------------------------------------
    1718
    1819IMPLICIT NONE 
    19  
    20    INTEGER :: nlaykim_up   ! Number of upper atm. layers for chemistry from GCM top to 4.5E-5 Pa (1300km)
    21    INTEGER :: nlaykim_tot  ! Number of total layers for chemistry from surface to 4.5E-5 Pa (1300km)
     20
     21   !! Hard-coded chemical species for Titan chemistry
     22   CHARACTER(len=10), DIMENSION(44), PARAMETER  :: cnames = &
     23     (/"H         ", "H2        ", "CH        ", "CH2s      ", "CH2       ", "CH3       ", &
     24       "CH4       ", "C2        ", "C2H       ", "C2H2      ", "C2H3      ", "C2H4      ", &
     25       "C2H5      ", "C2H6      ", "C3H3      ", "C3H5      ", "C3H6      ", "C3H7      ", &
     26       "C4H       ", "C4H3      ", "C4H4      ", "C4H2s     ", "CH2CCH2   ", "CH3CCH    ", &
     27       "C3H8      ", "C4H2      ", "C4H6      ", "C4H10     ", "AC6H6     ", "C3H2      ", &
     28       "C4H5      ", "AC6H5     ", "N2        ", "N4S       ", "CN        ", "HCN       ", &
     29       "H2CN      ", "CHCN      ", "CH2CN     ", "CH3CN     ", "C3N       ", "HC3N      ", &
     30       "NCCN      ", "C4N2      "/)
     31   !! Hard-coded chemical species molar mass (g.mol-1), shares the same indexing than cnames.
     32   REAL, DIMENSION(44), PARAMETER               :: cmmol = (/ &
     33       1.01   , 2.0158, 13.02, 14.03, 14.03, 15.03, 16.04  , 24.02, 25.03, 26.04  , 27.05  , &
     34       28.05  , 29.06 , 30.07, 39.06, 41.07, 42.08, 43.09  , 49.05, 51.07, 52.08  , 50.06  , &
     35       40.07  , 40.07 , 44.11, 50.06, 54.09, 58.13, 78.1136, 38.05, 53.07, 77.1136, 28.0134, &
     36       14.01  , 26.02 , 27.04, 28.05, 39.05, 40.04, 41.05  , 50.04, 51.05, 52.04  , 76.1   /)
     37   
     38   ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     39   !  Upper chemistry
     40   ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     41   
     42   INTEGER, SAVE :: nlaykim_up   ! Number of upper atm. layers for chemistry from GCM top to 4.5E-5 Pa (1300km)
     43   INTEGER, SAVE :: nlaykim_tot  ! Number of total layers for chemistry from surface to 4.5E-5 Pa (1300km)
    2244!$OMP_THREADPRIVATE(nlaykim_up,nlay_kim_tot)
    2345
     
    3355!$OMP_THREADPRIVATE(ykim_up)
    3456
     57CONTAINS
     58
     59  SUBROUTINE ini_comchem_h(ngrid)
     60 
     61  IMPLICIT NONE
     62 
     63    include "dimensions.h"
     64 
     65    INTEGER,INTENT(IN) :: ngrid ! number of atmospheric columns
     66 
     67    nlaykim_tot = nlaykim_up + llm
     68 
     69    IF (.NOT.allocated(preskim)) ALLOCATE(preskim(nlaykim_up))
     70    IF (.NOT.allocated(zlay_kim)) ALLOCATE(zlay_kim(ngrid,nlaykim_tot))
     71    IF (.NOT.allocated(ykim_up)) ALLOCATE(ykim_up(44,ngrid,nlaykim_up))
     72 
     73  END SUBROUTINE ini_comchem_h
     74
     75
    3576END MODULE comchem_h
  • trunk/LMDZ.TITAN/libf/phytitan/phyetat0_mod.F90

    r1789 r1894  
    264264endif ! of if (nq.ge.1)
    265265
    266 
    267266if (startphy_file) then
    268267  ! Call to soil_settings, in order to read soil temperatures,
     
    270269  call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
    271270endif ! of if (startphy_file)
     271
     272! Upper chemistry
     273if (startphy_file) then
     274  ! Call to soil_settings, in order to read upper chemistry
     275  ! pressure grid as well as composition fields
     276  call chem_settings(nid_start,ngrid,indextime)
     277endif ! of if (startphy_file)
     278
    272279!
    273280! close file:
  • trunk/LMDZ.TITAN/libf/phytitan/phyredem.F90

    r1889 r1894  
    143143  use iostart, only : open_restartphy, close_restartphy, &
    144144                      put_var, put_field
     145  use comchem_h, only: cnames, ykim_up
    145146  use tracer_h, only: noms
     147  use callkeys_mod, only: callchim
    146148
    147149  implicit none
     
    185187  call put_field("tankCH4","Depth of methane tank",tankCH4)
    186188 
    187 ! tracers
     189  ! Tracers
    188190  if (nq>0) then
    189191    do iq=1,nq
     
    191193    enddo
    192194  endif ! of if (nq>0)
    193 
     195 
     196  ! Upper chemistry
     197  if (callchim) then
     198    do iq=1,44
     199      call put_field(trim(cnames(iq))//"_up",trim(cnames(iq))//" in upper atmosphere",ykim_up(iq,:,:))
     200    enddo
     201  endif ! of if callchim
     202 
    194203! close file
    195204      CALL close_restartphy
  • trunk/LMDZ.TITAN/libf/phytitan/tracer_h.F90

    r1843 r1894  
    6868    USE callkeys_mod
    6969    USE comcstfi_mod, only: mugaz
     70    USE comchem_h, only: cnames, cmmol
    7071    IMPLICIT NONE
    7172
     
    7677    LOGICAL                                      :: verb,found
    7778    CHARACTER(len=20)                            :: str
    78     !! Hard-coded chemical species for Titan chemistry
    79     CHARACTER(len=10), DIMENSION(44), PARAMETER  :: cnames = &
    80       (/"H         ", "H2        ", "CH        ", "CH2s      ", "CH2       ", "CH3       ", &
    81         "CH4       ", "C2        ", "C2H       ", "C2H2      ", "C2H3      ", "C2H4      ", &
    82         "C2H5      ", "C2H6      ", "C3H3      ", "C3H5      ", "C3H6      ", "C3H7      ", &
    83         "C4H       ", "C4H3      ", "C4H4      ", "C4H2s     ", "CH2CCH2   ", "CH3CCH    ", &
    84         "C3H8      ", "C4H2      ", "C4H6      ", "C4H10     ", "AC6H6     ", "C3H2      ", &
    85         "C4H5      ", "AC6H5     ", "N2        ", "N4S       ", "CN        ", "HCN       ", &
    86         "H2CN      ", "CHCN      ", "CH2CN     ", "CH3CN     ", "C3N       ", "HC3N      ", &
    87         "NCCN      ", "C4N2      "/)
    88     !! Hard-coded chemical species molar mass (g.mol-1), shares the same indexing than cnames.
    89     REAL, DIMENSION(44), PARAMETER               :: cmmol = (/ &
    90         1.01   , 2.0158, 13.02, 14.03, 14.03, 15.03, 16.04  , 24.02, 25.03, 26.04  , 27.05  , &
    91         28.05  , 29.06 , 30.07, 39.06, 41.07, 42.08, 43.09  , 49.05, 51.07, 52.08  , 50.06  , &
    92         40.07  , 40.07 , 44.11, 50.06, 54.09, 58.13, 78.1136, 38.05, 53.07, 77.1136, 28.0134, &
    93         14.01  , 26.02 , 27.04, 28.05, 39.05, 40.04, 41.05  , 50.04, 51.05, 52.04  , 76.1   /)
    9479
    9580    INTEGER :: i,j,n
Note: See TracChangeset for help on using the changeset viewer.