source: trunk/LMDZ.PLUTO/libf/phypluto/tracer_h.F90 @ 3557

Last change on this file since 3557 was 3557, checked in by debatzbr, 2 weeks ago

Miscellaneous cleans + Set-up the physics for the implementation of the microphysical model.

File size: 9.8 KB
RevLine 
[3184]1
2       module tracer_h
[3557]3       !!------------------------------------------------------------------------------------------------------
4       !! Stores data related to physics tracers.
5       !!
6       !! The module provides additional methods:
7       !!   - indexoftracer : search for the index of a tracer in the global table (tracers_h:noms) by name.
8       !!   - nameoftracer  : get the name of tracer from a given index (of the global table).
9       !!   - dumptracers   : print the names of all tracers indexes given in argument.
10       !!------------------------------------------------------------------------------------------------------
[3184]11       implicit none
12
[3557]13       integer, save :: nqtot  ! total number of tracers
14       integer, save :: nesp   ! number of species in the chemistry
15       integer, save :: ngt    ! number of generic tracers
[3184]16       integer, save :: n_rgcs ! number of Radiative Generic Condensable Species
17!$OMP THREADPRIVATE(nqtot,nesp,ngt,n_rgcs)
18
19       logical :: moderntracdef=.false. ! Standard or modern traceur.def
20!$OMP THREADPRIVATE(moderntracdef)
21
[3557]22       character*30, save, allocatable :: noms(:)! name of the tracer
23       real, save, allocatable :: mmol(:)        ! mole mass of tracer (g/mol)
24       real, save, allocatable :: aki(:)         ! to compute coefficient of thermal concduction if photochem
25       real, save, allocatable :: cpi(:)         ! to compute cpnew in concentration.F if photochem
26       real, save, allocatable :: radius(:)      ! dust and ice particle radius (m)
27       real, save, allocatable :: rho_q(:)       ! tracer densities (kg.m-3)
28       real, save, allocatable :: qext(:)        ! Single Scat. Extinction coeff at 0.67 um
[3184]29       real, save, allocatable :: alpha_lift(:)  ! saltation vertical flux/horiz flux ratio (m-1)
30       real, save, allocatable :: alpha_devil(:) ! lifting coeeficient by dust devil
[3557]31       real, save, allocatable :: qextrhor(:)    ! Intermediate for computing opt. depth from q
[3184]32
33       real,save :: varian      ! Characteristic variance of log-normal distribution
[3557]34       real,save :: r3n_q       ! used to compute r0 from number and mass mixing ratio
35       real,save :: rho_dust    ! Mars dust density (kg.m-3)
[3184]36       real,save :: rho_ice     ! Water ice density (kg.m-3)
[3557]37       real,save :: rho_ch4_ice ! ch4 ice density (kg.m-3)
38       real,save :: rho_co_ice  ! co ice density (kg.m-3)
39       real,save :: rho_n2      ! N2 ice density (kg.m-3)
40       real,save :: lw_ch4      ! Latent heat CH4 gas -> solid
41       real,save :: lw_co       ! Latent heat CO gas -> solid
42       real,save :: lw_n2       ! Latent heat N2 gas -> solid
[3195]43       integer,save :: nmono
[3184]44       real,save :: ref_r0        ! for computing reff=ref_r0*r0 (in log.n. distribution)
45!$OMP THREADPRIVATE(noms,mmol,aki,cpi,radius,rho_q,qext,alpha_lift,alpha_devil,qextrhor, &
[3195]46        !$OMP varian,r3n_q,rho_dust,rho_ice,rho_n2,lw_n2,ref_r0)
[3184]47
48       integer, save, allocatable :: is_chim(:) ! 1 if tracer used in chemistry, else 0
49       integer, save, allocatable :: is_rad(:)  ! 1 if   ""    ""  in radiative transfer, else 0
50!$OMP THREADPRIVATE(is_chim,is_rad)
51
52       integer, save, allocatable :: is_recomb(:)      ! 1 if tracer used in recombining scheme, else 0 (if 1, must have is_rad=1)
53       integer, save, allocatable :: is_recomb_qset(:) ! 1 if tracer k-corr assume predefined vmr, else 0 (if 1, must have is_recomb=1)
54       integer, save, allocatable :: is_recomb_qotf(:) ! 1 if tracer recombination is done on-the-fly, else 0 (if 1, must have is_recomb_qset=0)
55!$OMP THREADPRIVATE(is_recomb,is_recomb_qset,is_recomb_qotf)
56       integer, save, allocatable :: is_condensable(:)      ! 1 if tracer is generic, else 0 (added LT)
57       integer,save,allocatable :: is_rgcs(:)               ! 1 if tracer is a radiative generic condensable specie, else 0 (added LT 2022)
[3557]58!$OMP THREADPRIVATE(is_condensable,is_rgcs)   !also added by LT
[3184]59       ! Lists of constants for condensable tracers
[3557]60       real, save, allocatable :: constants_mass(:)                 ! molecular mass of the specie (g/mol)
[3275]61       real, save, allocatable :: constants_delta_gasH(:)           ! Enthalpy of vaporization (J/mol)
[3184]62       real, save, allocatable :: constants_Tref(:)                 ! Ref temperature for Clausis-Clapeyron (K)
63       real, save, allocatable :: constants_Pref(:)                 ! Reference pressure for Clausius Clapeyron (Pa)
[3557]64       real, save, allocatable :: constants_epsi_generic(:)         ! fractionnal molecular mass (m/mugaz)
65       real, save, allocatable :: constants_RLVTT_generic(:)        ! Latent heat of vaporization (J/kg)
[3184]66       real, save, allocatable :: constants_metallicity_coeff(:)    ! Coefficient to take into account the metallicity
[3557]67       real, save, allocatable :: constants_RCPV_generic(:)         ! specific heat capacity of the tracer vapor at Tref
[3275]68!$OMP THREADPRIVATE(constants_mass,constants_delta_gasH,constants_Tref)
[3184]69!$OMP THREADPRIVATE(constants_Pref,constants_epsi_generic)
70!$OMP THREADPRIVATE(constants_RLVTT_generic,constants_metallicity_coeff,constants_RCPV_generic)
71
72! tracer indexes: these are initialized in initracer and should be 0 if the
73!                 corresponding tracer does not exist
[3195]74
[3557]75       ! Pluto chemistry
[3195]76       integer,save :: igcm_co_gas
[3184]77       integer,save :: igcm_n2
78       integer,save :: igcm_ar
[3195]79       integer,save :: igcm_ch4_gas ! methane gas
[3557]80!$OMP THREADPRIVATE(igcm_co_gas,igcm_n2,igcm_ar,igcm_ch4_gas)
81       ! Other tracers
82       integer,save :: igcm_ar_n2   ! for simulations using co2 + neutral gaz
[3195]83       integer,save :: igcm_ch4_ice ! methane ice
[3557]84       integer,save :: igcm_co_ice  ! CO ice
85!$OMP THREADPRIVATE(igcm_ar_n2,igcm_ch4_ice,igcm_co_ice)
[3195]86       integer,save :: igcm_prec_haze
87       integer,save :: igcm_haze
88       integer,save :: igcm_haze10
89       integer,save :: igcm_haze30
90       integer,save :: igcm_haze50
91       integer,save :: igcm_haze100
[3557]92!$OMP THREADPRIVATE(igcm_prec_haze,igcm_haze,igcm_haze10,igcm_haze30,igcm_haze50,igcm_haze100)
[3195]93       integer,save :: igcm_eddy1e6
94       integer,save :: igcm_eddy1e7
95       integer,save :: igcm_eddy5e7
96       integer,save :: igcm_eddy1e8
97       integer,save :: igcm_eddy5e8
[3557]98!$OMP THREADPRIVATE(igcm_eddy1e6,igcm_eddy1e7,igcm_eddy5e7,igcm_eddy1e8,igcm_eddy5e8)
[3184]99
[3557]100       ! Microphysical model
101       integer, save :: nmicro = 0                 !! Number of microphysics tracers.
102       integer, save, allocatable :: micro_indx(:) !! Indexes of all microphysical tracers
103!$OMP THREADPRIVATE(nmicro)
[3184]104
[3557]105       CONTAINS
[3184]106
[3557]107       FUNCTION indexoftracer(name, sensitivity) RESULT(idx)
108          !! Get the index of a tracer by name.
109          !!
110          !! The function searches in the global tracer table (tracer_h:noms)
111          !! for the given name and returns the first index matching "name".
112          !!
113          !! If no name in the table matches the given one, -1 is returned !
114          IMPLICIT NONE
115          CHARACTER(len=*), INTENT(in)  :: name         !! Name of the tracer to search.
116          LOGICAL, OPTIONAL, INTENT(in) :: sensitivity  !! Case sensitivity (true by default).
117          INTEGER                       :: idx          !! Index of the first tracer matching name or -1 if not found.
118          LOGICAL                       :: zsens
119          INTEGER                       :: j
120          CHARACTER(len=LEN(name))      :: zname
121          zsens = .true. ; IF(PRESENT(sensitivity)) zsens = sensitivity
122          idx = -1
123          IF (.NOT.ALLOCATED(noms)) RETURN
124          IF (zsens) THEN
125             DO j=1,SIZE(noms)
126                IF (TRIM(noms(j)) == TRIM(name)) THEN
127                   idx = j ; RETURN
128                ENDIF
129             ENDDO
130          ELSE
131             zname = to_lower(name)
132             DO j=1,SIZE(noms)
133                IF (TRIM(to_lower(noms(j))) == TRIM(zname)) THEN
134                   idx = j ; RETURN
135                ENDIF
136             ENDDO
137          ENDIF
138
139          CONTAINS
140
141          FUNCTION to_lower(istr) RESULT(ostr)
142             !! Lower case conversion function.
143             IMPLICIT NONE
144             CHARACTER(len=*), INTENT(in) :: istr
145             CHARACTER(len=LEN(istr))     :: ostr
146             INTEGER                      :: i,ic
147             ostr = istr
148             DO i = 1, LEN_TRIM(istr)
149                ic = ICHAR(istr(i:i))
150                IF (ic >= 65 .AND. ic < 90) ostr(i:i) = char(ic + 32)
151             ENDDO
152          END FUNCTION to_lower
153       END FUNCTION indexoftracer
154
155       FUNCTION nameoftracer(indx) RESULT(name)
156          !! Get the name of a tracer by index.
157          !!
158          !! The function searches in the global tracer table (tracer_h:noms)
159          !! and returns the name of the tracer at given index.
160          !!
161          !! If the index is out of range an empty string is returned.
162          IMPLICIT NONE
163          INTEGER, INTENT(in) :: indx   !! Index of the tracer name to retrieve.
164          CHARACTER(len=30)   :: name   !! Name of the tracer at given index.
165          name = ''
166          IF (.NOT.ALLOCATED(noms)) RETURN
167          IF (indx <= 0 .OR. indx > SIZE(noms)) RETURN
168          name = noms(indx)
169       END FUNCTION nameoftracer
170
171       SUBROUTINE dumptracers(indexes)
172          !! Print the names of the given list of tracers indexes.
173          INTEGER, DIMENSION(:), INTENT(in) :: indexes
174          INTEGER :: i,idx
175          CHARACTER(len=:), ALLOCATABLE :: suffix
176
177          IF (.NOT.ALLOCATED(noms)) THEN
178             WRITE(*,'(a)') "[tracers_h:dump_tracers] warning: 'noms' is not allocated, initracer has not be called yet"
179             RETURN
180          ENDIF
181
182          DO i=1,size(indexes)
183             idx = indexes(i)
184             IF (ANY(micro_indx == idx)) THEN
185                suffix = ' (micro)'
186             ELSE
187                suffix=" ()"
188             ENDIF
189             WRITE(*,'(I5,(a),I6,(a))') i," -> ",idx ," : "//TRIM(noms(idx))//suffix
190          ENDDO
191       END SUBROUTINE dumptracers
192
193       end module tracer_h
Note: See TracBrowser for help on using the repository browser.