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

Last change on this file since 3572 was 3572, checked in by debatzbr, 3 weeks ago

Remove generic_aerosols and generic_condensation, along with their related variables (useless). RENAME THE VARIABLE AEROHAZE TO OPTICHAZE.

File size: 9.5 KB
Line 
1
2       module tracer_h
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       !!------------------------------------------------------------------------------------------------------
11       implicit none
12
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
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
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
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
31       real, save, allocatable :: qextrhor(:)    ! Intermediate for computing opt. depth from q
32
33       real,save :: varian      ! Characteristic variance of log-normal distribution
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)
36       real,save :: rho_ice     ! Water ice density (kg.m-3)
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
43       integer,save :: nmono
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, &
46        !$OMP varian,r3n_q,rho_dust,rho_ice,rho_n2,lw_n2,ref_r0)
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)
58!$OMP THREADPRIVATE(is_condensable,is_rgcs)   !also added by LT
59       ! Lists of constants for condensable tracers
60       real, save, allocatable :: constants_mass(:)                 ! molecular mass of the specie (g/mol)
61       real, save, allocatable :: constants_delta_gasH(:)           ! Enthalpy of vaporization (J/mol)
62       real, save, allocatable :: constants_Tref(:)                 ! Ref temperature for Clausis-Clapeyron (K)
63       real, save, allocatable :: constants_Pref(:)                 ! Reference pressure for Clausius Clapeyron (Pa)
64       real, save, allocatable :: constants_RLVTT_generic(:)        ! Latent heat of vaporization (J/kg)
65       real, save, allocatable :: constants_RCPV_generic(:)         ! specific heat capacity of the tracer vapor at Tref
66!$OMP THREADPRIVATE(constants_mass,constants_delta_gasH,constants_Tref)
67!$OMP THREADPRIVATE(constants_Pref)
68!$OMP THREADPRIVATE(constants_RLVTT_generic,constants_RCPV_generic)
69
70! tracer indexes: these are initialized in initracer and should be 0 if the
71!                 corresponding tracer does not exist
72
73       ! Pluto chemistry
74       integer,save :: igcm_co_gas
75       integer,save :: igcm_n2
76       integer,save :: igcm_ar
77       integer,save :: igcm_ch4_gas ! methane gas
78!$OMP THREADPRIVATE(igcm_co_gas,igcm_n2,igcm_ar,igcm_ch4_gas)
79       ! Other tracers
80       integer,save :: igcm_ar_n2   ! for simulations using co2 + neutral gaz
81       integer,save :: igcm_ch4_ice ! methane ice
82       integer,save :: igcm_co_ice  ! CO ice
83!$OMP THREADPRIVATE(igcm_ar_n2,igcm_ch4_ice,igcm_co_ice)
84       integer,save :: igcm_prec_haze
85       integer,save :: igcm_haze
86       integer,save :: igcm_haze10
87       integer,save :: igcm_haze30
88       integer,save :: igcm_haze50
89       integer,save :: igcm_haze100
90!$OMP THREADPRIVATE(igcm_prec_haze,igcm_haze,igcm_haze10,igcm_haze30,igcm_haze50,igcm_haze100)
91       integer,save :: igcm_eddy1e6
92       integer,save :: igcm_eddy1e7
93       integer,save :: igcm_eddy5e7
94       integer,save :: igcm_eddy1e8
95       integer,save :: igcm_eddy5e8
96!$OMP THREADPRIVATE(igcm_eddy1e6,igcm_eddy1e7,igcm_eddy5e7,igcm_eddy1e8,igcm_eddy5e8)
97
98       ! Microphysical model
99       integer, save :: nmicro = 0                 !! Number of microphysics tracers.
100       integer, save, allocatable :: micro_indx(:) !! Indexes of all microphysical tracers
101!$OMP THREADPRIVATE(nmicro)
102
103       CONTAINS
104
105       FUNCTION indexoftracer(name, sensitivity) RESULT(idx)
106          !! Get the index of a tracer by name.
107          !!
108          !! The function searches in the global tracer table (tracer_h:noms)
109          !! for the given name and returns the first index matching "name".
110          !!
111          !! If no name in the table matches the given one, -1 is returned !
112          IMPLICIT NONE
113          CHARACTER(len=*), INTENT(in)  :: name         !! Name of the tracer to search.
114          LOGICAL, OPTIONAL, INTENT(in) :: sensitivity  !! Case sensitivity (true by default).
115          INTEGER                       :: idx          !! Index of the first tracer matching name or -1 if not found.
116          LOGICAL                       :: zsens
117          INTEGER                       :: j
118          CHARACTER(len=LEN(name))      :: zname
119          zsens = .true. ; IF(PRESENT(sensitivity)) zsens = sensitivity
120          idx = -1
121          IF (.NOT.ALLOCATED(noms)) RETURN
122          IF (zsens) THEN
123             DO j=1,SIZE(noms)
124                IF (TRIM(noms(j)) == TRIM(name)) THEN
125                   idx = j ; RETURN
126                ENDIF
127             ENDDO
128          ELSE
129             zname = to_lower(name)
130             DO j=1,SIZE(noms)
131                IF (TRIM(to_lower(noms(j))) == TRIM(zname)) THEN
132                   idx = j ; RETURN
133                ENDIF
134             ENDDO
135          ENDIF
136
137          CONTAINS
138
139          FUNCTION to_lower(istr) RESULT(ostr)
140             !! Lower case conversion function.
141             IMPLICIT NONE
142             CHARACTER(len=*), INTENT(in) :: istr
143             CHARACTER(len=LEN(istr))     :: ostr
144             INTEGER                      :: i,ic
145             ostr = istr
146             DO i = 1, LEN_TRIM(istr)
147                ic = ICHAR(istr(i:i))
148                IF (ic >= 65 .AND. ic < 90) ostr(i:i) = char(ic + 32)
149             ENDDO
150          END FUNCTION to_lower
151       END FUNCTION indexoftracer
152
153       FUNCTION nameoftracer(indx) RESULT(name)
154          !! Get the name of a tracer by index.
155          !!
156          !! The function searches in the global tracer table (tracer_h:noms)
157          !! and returns the name of the tracer at given index.
158          !!
159          !! If the index is out of range an empty string is returned.
160          IMPLICIT NONE
161          INTEGER, INTENT(in) :: indx   !! Index of the tracer name to retrieve.
162          CHARACTER(len=30)   :: name   !! Name of the tracer at given index.
163          name = ''
164          IF (.NOT.ALLOCATED(noms)) RETURN
165          IF (indx <= 0 .OR. indx > SIZE(noms)) RETURN
166          name = noms(indx)
167       END FUNCTION nameoftracer
168
169       SUBROUTINE dumptracers(indexes)
170          !! Print the names of the given list of tracers indexes.
171          INTEGER, DIMENSION(:), INTENT(in) :: indexes
172          INTEGER :: i,idx
173          CHARACTER(len=:), ALLOCATABLE :: suffix
174
175          IF (.NOT.ALLOCATED(noms)) THEN
176             WRITE(*,'(a)') "[tracers_h:dump_tracers] warning: 'noms' is not allocated, initracer has not be called yet"
177             RETURN
178          ENDIF
179
180          DO i=1,size(indexes)
181             idx = indexes(i)
182             IF (ANY(micro_indx == idx)) THEN
183                suffix = ' (micro)'
184             ELSE
185                suffix=" ()"
186             ENDIF
187             WRITE(*,'(I5,(a),I6,(a))') i," -> ",idx ," : "//TRIM(noms(idx))//suffix
188          ENDDO
189       END SUBROUTINE dumptracers
190
191       end module tracer_h
Note: See TracBrowser for help on using the repository browser.