source: trunk/LMDZ.TITAN/libf/phytitan/comchem_h.F90 @ 3529

Last change on this file since 3529 was 2793, checked in by emillour, 2 years ago

Titan physics:
Fix some OpenMP typos and inconsistencies spoted when compiling (even without OpenMP) on Irene.
Some further run-time checking in debug mode might be needed to ensure everything is indeed OK for OpenMP.
EM

File size: 6.2 KB
Line 
1MODULE comchem_h
2
3! -------------------------------------------------------------------------------------------------------------
4! Purpose : + Stores data relative to :  * 1. Chemistry in the GCM
5! -------                                * 2. Upper chemistry pressure grid
6!                                        * 3. Coupling with C photochem. module ( cf calchim.F90)
7!           
8!           + Also contains a routine of initialization for chemistry in the GCM.
9!
10!           + NB : For newstart there is a specific comchem_newstart_h module.
11!
12! Author : Jan Vatant d'Ollone (2017-18)
13! ------
14!
15! NB : A given order is assumed for the 44 chemistry tracers :
16!      H, H2, CH, CH2s, CH2, CH3, CH4, C2, C2H, C2H2, C2H3, C2H4, C2H5,
17!      C2H6, C3H3, C3H5, C3H6, C3H7, C4H, C4H3, C4H4, C4H2s, CH2CCH2,
18!      CH3CCH, C3H8, C4H2, C4H6, C4H10, AC6H6, C3H2, C4H5, AC6H5, N2,
19!      N4S, CN, HCN, H2CN, CHCN, CH2CN, CH3CN, C3N, HC3N, NCCN, C4N2
20!
21!       
22! IMPORTANT : Advected chem. tracers are in MASS fraction but upper fields ykim_up are in MOLAR fraction !
23!
24! -------------------------------------------------------------------------------------------------------------
25
26IMPLICIT NONE 
27
28   ! ~~~~~~~~~~~~~~~~~~~~~~~~
29   ! 1. Chemistry in the GCM
30   ! ~~~~~~~~~~~~~~~~~~~~~~~~
31
32   !! Hard-coded number of chemical species for Titan chemistry
33   INTEGER, PARAMETER :: nkim = 43
34
35   !! Hard-coded chemical species for Titan chemistry
36   CHARACTER(len=10), DIMENSION(nkim), PARAMETER  :: cnames = &
37     (/"H         ", "H2        ", "CH        ", "CH2s      ", "CH2       ", "CH3       ", &
38       "CH4       ", "C2        ", "C2H       ", "C2H2      ", "C2H3      ", "C2H4      ", &
39       "C2H5      ", "C2H6      ", "C3H3      ", "C3H5      ", "C3H6      ", "C3H7      ", &
40       "C4H       ", "C4H3      ", "C4H4      ", "CH2CCH2   ", "CH3CCH    ", "C3H8      ", &
41       "C4H2      ", "C4H6      ", "C4H10     ", "AC6H6     ", "C3H2      ", "C4H5      ", &
42       "AC6H5     ", "N2        ", "N4S       ", "CN        ", "HCN       ", "H2CN      ", &
43       "CHCN      ", "CH2CN     ", "CH3CN     ", "C3N       ", "HC3N      ", "NCCN      ", &
44       "C4N2      "/)
45   !! Hard-coded chemical species for Titan chemistry + "HV" specie for the photochem module.
46   CHARACTER(len=10), DIMENSION(nkim+1)  :: nomqy_c ! Initialized in calchim with null terminator
47   !! Hard-coded chemical species molar mass (g.mol-1), shares the same indexing than cnames.
48   REAL, DIMENSION(nkim), PARAMETER               :: cmmol = (/ &
49       1.01   , 2.0158, 13.02, 14.03, 14.03, 15.03, 16.04  , 24.02, 25.03, 26.04  , 27.05  , &
50       28.05  , 29.06 , 30.07, 39.06, 41.07, 42.08, 43.09  , 49.05, 51.07, 52.08  , 40.07  , &
51       40.07 , 44.11, 50.06, 54.09, 58.13, 78.1136, 38.05, 53.07, 77.1136, 28.0134, 14.01  , &
52       26.02 , 27.04, 28.05, 39.05, 40.04, 41.05  , 50.04, 51.05, 52.04  , 76.1   /)
53
54   !! Hard-coded molar fraction of surface methane
55   REAL, PARAMETER :: botCH4 = 0.0565 ! From Niemann et al. 2010 - Huygens GCMS measurements
56   
57
58
59   ! ~~~~~~~~~~~~~~~~~~~~~~~~~~
60   !  2. Upper chemistry grid
61   ! ~~~~~~~~~~~~~~~~~~~~~~~~~~
62
63   INTEGER, SAVE :: nlaykim_up   ! Number of upper atm. layers for chemistry from GCM top to 4.5E-5 Pa (1300km)
64   INTEGER, SAVE :: nlaykim_tot  ! Number of total layers for chemistry from surface to 4.5E-5 Pa (1300km)
65!$OMP THREADPRIVATE(nlaykim_up,nlaykim_tot)
66
67   ! NB : For the startfile we use nlaykim_up grid (upper atm) and for outputs we use nlaykim_tot grid (all layers)
68 
69   REAL*8, PARAMETER :: grkim_dz = 10.0 ! Vertical discretization of the upper chemistry grid (km)
70
71   REAL,SAVE,ALLOCATABLE,DIMENSION(:)     :: preskim  ! Pressure (Pa) of upper chemistry (mid)-layers
72   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:)   :: zlaykim  ! Pseudo-altitude (km) of upper chemistry (mid)-layers
73   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:,:) :: ykim_up  ! Upper chemistry fields (mol/mol)
74   
75   ! These "_tot" fields are for output only
76   REAL,SAVE,ALLOCATABLE,DIMENSION(:)     :: preskim_tot  ! Pressure (Pa) of total chemistry (mid)-layers
77   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:)   :: zlaykim_tot  ! Pseudo-altitude (km) of total chemistry (mid)-layers
78   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:,:) :: ykim_tot     ! Total chemistry fields (mol/mol)
79   
80!$OMP THREADPRIVATE(preskim,zlaykim,ykim_up)
81!$OMP THREADPRIVATE(preskim_tot,zlaykim_tot,ykim_tot)
82
83   ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
84   !  3. Interface with photochemical module (cf calchim.F90)
85   ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
86   
87   ! These 3 parameters as well as nkim above, MUST match titan.h in chimtitan !!
88   INTEGER, PARAMETER :: nd_kim   = 55     ! Number of photodissociations
89   INTEGER, PARAMETER :: nr_kim   = 330    ! Number of reactions in chemistry scheme
90   INTEGER, PARAMETER :: nlrt_kim = 650    ! For the UV rad. transf., 650 levels of 2 km
91
92   !! Hardcoded latitude discretisation for actinic fluxes - MUST be coherent with disso.c input files !!
93   INTEGER, PARAMETER                         :: nlat_actfluxes = 49
94   REAL, DIMENSION(nlat_actfluxes), PARAMETER :: lat_actfluxes  = (/ &
95      90.0 ,  86.25,  82.5 ,  78.75,  75.0 ,  71.25,  67.5 ,  63.75,  60.0 ,  56.25,  52.5 ,  48.75, &
96      45.0 ,  41.25,  37.5 ,  33.75,  30.0 ,  26.25,  22.5 ,  18.75,  15.0 ,  11.25,   7.5 ,   3.75, &
97       0.0 ,  -3.75,  -7.5 , -11.25, -15.0 , -18.75, -22.5 , -26.25, -30.0 , -33.75, -37.5 , -41.25, &
98     -45.0 , -48.75, -52.5 , -56.25, -60.0 , -63.75, -67.5 , -71.25, -75.0 , -78.75, -82.5 , -86.25, &
99     -90.0 /)
100   
101
102CONTAINS
103
104  SUBROUTINE ini_comchem_h(ngrid)
105 
106  IMPLICIT NONE
107 
108    include "dimensions.h"
109 
110    INTEGER,INTENT(IN) :: ngrid ! number of atmospheric columns
111 
112    nlaykim_tot = nlaykim_up + llm
113 
114    IF (.NOT.allocated(preskim)) ALLOCATE(preskim(nlaykim_up))
115    IF (.NOT.allocated(zlaykim)) ALLOCATE(zlaykim(ngrid,nlaykim_up))
116    IF (.NOT.allocated(ykim_up)) ALLOCATE(ykim_up(nkim,ngrid,nlaykim_up))
117   
118    IF (.NOT.allocated(preskim_tot)) ALLOCATE(preskim_tot(nlaykim_tot))
119    IF (.NOT.allocated(zlaykim_tot)) ALLOCATE(zlaykim_tot(ngrid,nlaykim_tot))
120    IF (.NOT.allocated(ykim_tot)) ALLOCATE(ykim_tot(nkim,ngrid,nlaykim_tot))
121 
122  END SUBROUTINE ini_comchem_h
123
124
125END MODULE comchem_h
Note: See TracBrowser for help on using the repository browser.