source: trunk/LMDZ.TITAN/libf/phytitan/tracer_h.F90 @ 1862

Last change on this file since 1862 was 1843, checked in by jvatant, 7 years ago

Enable tracers management in 1D
--JVO

File size: 12.4 KB
Line 
1
2MODULE tracer_h
3  !! Stores data related to physics tracers.
4  !!
5  !! The module stores public global variables related to the number of tracers
6  !! available in the physics and their kind:
7  !!
8  !! Currently, tracers can be used either for chemistry process (nchimi) or
9  !! microphysics (nmicro).
10  !!
11  !! The subroutine "initracer2" initializes and performs sanity check of
12  !! the tracer definitions given in traceur.def and the required tracers in physics
13  !! (based on the run parameters).
14  !!
15  !! The module provides additional methods:
16  !!
17  !!   - indexOfTracer : search for the index of a tracer in the global table (tracers_h:noms) by name.
18  !!   - nameOfTracer  : get the name of tracer from a given index (of the global table).
19  !!   - dumpTracers   : print the names of all tracers indexes given in argument.
20  !!
21  IMPLICIT NONE
22
23  INTEGER, SAVE :: nqtot_p  = 0 !! Total number of physical tracers
24  INTEGER, SAVE :: nmicro = 0 !! Number of microphysics tracers.
25  INTEGER, SAVE :: nice   = 0 !! Number of microphysics ice tracers (subset of nmicro).
26  INTEGER, SAVE :: nchimi = 0 !! Number of chemical (gaz species) tracers.
27  !$OMP THREADPRIVATE(nqtot_p,nmicro,nice,nchimi)
28
29  INTEGER, DIMENSION(:), ALLOCATABLE, SAVE :: chimi_indx  !! Indexes of all chemical species tracers
30  INTEGER, DIMENSION(:), ALLOCATABLE, SAVE :: micro_indx  !! Indexes of all microphysical tracers
31  INTEGER, DIMENSION(:), ALLOCATABLE, SAVE :: ices_indx   !! Indexes of all ice microphysical tracers
32
33  CHARACTER(len=20), DIMENSION(:), ALLOCATABLE, SAVE :: noms      !! name of the tracer
34  REAL, DIMENSION(:), ALLOCATABLE, SAVE              :: mmol      !! mole mass of tracer(g/mol-1)
35  REAL, DIMENSION(:), ALLOCATABLE, SAVE              :: rat_mmol  !! molar mass ratio
36  REAL, DIMENSION(:), ALLOCATABLE, SAVE              :: rho_q     !! tracer densities (kg.m-3)
37  !$OMP THREADPRIVATE(noms,mmol,rat_mmol,rho_q)
38
39
40
41  ! tracer indexes: these are initialized in initracer and should be 0 if the
42  !                 corresponding tracer does not exist
43
44
45  CONTAINS
46
47  SUBROUTINE initracer2(nq,nametrac,talk_to_me)
48    !! Initialize tracer names and attributes.
49    !!
50    !! The method initializes the list of tracer names used in the physics from their
51    !! dynamics counterpart.
52    !!
53    !! In addition, it initializes arrays of indexes for the different sub-processs of the physics:
54    !!
55    !!   - tracers_h:micro_indxs, the array of tracers indexes used for the microphysics.
56    !!   - tracers_h:chimi_indxs, the array of tracers indexes used for the chemistry.
57    !!
58    !! The method also initializes the molar mass array (tracers_h:mmol) for the chemistry and the
59    !! molar mass ratio (tracers_h:rat_mmol).
60    !!
61    !! @note
62    !! Strict checking of chemical species name is performed here if the chemistry is activated
63    !! (see callchim variable). All the values of 'cnames' must be found in the tracers names
64    !! related to chemistry.
65    !! @note
66    !! Tests are more permissive for the microphysics and is only based on the mimimum number of
67    !! tracers expected. Strict name checking is performed in inimufi.
68    USE callkeys_mod
69    USE comcstfi_mod, only: mugaz
70    IMPLICIT NONE
71
72    INTEGER, INTENT(in)                          :: nq         !! Total number of tracers (fixed at compile time)
73    character(len=20), DIMENSION(nq), INTENT(in) :: nametrac   !! name of the tracer from dynamics (from 'traceurs.def')
74    LOGICAL, INTENT(in), OPTIONAL                :: talk_to_me !! Enable verbose mode.
75
76    LOGICAL                                      :: verb,found
77    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   /)
94
95    INTEGER :: i,j,n
96
97    verb = .true. ; IF (PRESENT(talk_to_me)) verb = talk_to_me
98
99    ! nqtot_p could be used everywhere in the physic :)
100    nqtot_p=nq
101
102    IF (.NOT.ALLOCATED(noms)) ALLOCATE(noms(nq))
103    noms(:)=nametrac(:)
104
105    IF (.NOT.ALLOCATED(rho_q)) ALLOCATE(rho_q(nq)) ! Defined for all tracers, currently initialized to 0.0
106    rho_q(:) = 0.0
107
108    ! Defined for all tracers, (actually) initialized only for chemical tracers
109    IF (.NOT.ALLOCATED(mmol)) ALLOCATE(mmol(nq))
110    IF (.NOT.ALLOCATED(rat_mmol)) ALLOCATE(rat_mmol(nq))
111    mmol(:)  = 0.0
112    rat_mmol(:) = 1.0
113
114    ! Compute number of microphysics tracers:
115    ! By convention they all have the prefix "mu_" (case sensitive !)
116    nmicro = 0
117    IF (callmufi) THEN
118      DO i=1,nq
119        str = noms(i)
120        IF (str(1:3) == "mu_") nmicro = nmicro+1
121      ENDDO
122      ! Checking the expected number of tracers:
123      !   no cloud:  4 ; w cloud :  4 + 2 + (1+)
124      ! Note that we do not make assumptions on the number of chemical species for clouds, this
125      ! will be checked in inimufi.
126      IF (callclouds) THEN
127        IF (nmicro < 7) THEN
128          WRITE(*,'((a),I3,(a))') "initracer2:error: Inconsistent number of microphysical tracers &
129            &(expected at least 7 tracers,",nmicro," given)"
130          CALL abort_gcm("initracer2", "inconsistent number of tracers", 42)
131          STOP
132        ENDIF
133      ELSE IF (nmicro < 4) THEN
134          WRITE(*,'((a),I3,(a))') "initracer2:error: Inconsistent number of microphysical tracers &
135            &(expected at least 4 tracers,",nmicro," given)"
136          CALL abort_gcm("initracer2", "inconsistent number of tracers", 42)
137      ELSE IF  (nmicro > 4) THEN
138        WRITE(*,'(a)') "initracer2:info: I was expecting only four tracers, you gave me &
139          &more. I'll just pretend nothing happen !"
140      ENDIF
141      ! microphysics indexes share the same values than original tracname.
142      IF (.NOT.ALLOCATED(micro_indx)) ALLOCATE(micro_indx(nmicro))
143      j = 1
144      DO i=1,nq
145        str = noms(i)
146        IF (str(1:3) == "mu_") THEN
147          micro_indx(j) = i
148          j=j+1
149        ENDIF
150      ENDDO
151    ELSE
152      IF (.NOT.ALLOCATED(micro_indx)) ALLOCATE(micro_indx(nmicro))
153    ENDIF
154
155    ! Compute number of chemical species:
156    !   simply assume that all other tracers ARE chemical species
157    nchimi = nqtot_p - nmicro
158
159    ! Titan chemistry requires exactly 44 tracers:
160    ! Test should be in callchim condition
161
162    IF (callchim) THEN
163      IF (nchimi < SIZE(cnames)) THEN
164        WRITE(*,*) "initracer2:error: Inconsistent number of chemical species given (",SIZE(cnames)," expected)"
165        CALL abort_gcm("initracer2", "inconsistent number of tracers", 42)
166      ENDIF
167      IF (.NOT.ALLOCATED(chimi_indx)) ALLOCATE(chimi_indx(nchimi))
168      n = 0 ! counter on chimi_indx
169      DO j=1,SIZE(cnames)
170        found = .false.
171        DO i=1,nq
172          IF (TRIM(cnames(j)) == TRIM(noms(i))) THEN
173            n = n + 1
174            chimi_indx(n) = i
175            mmol(i) = cmmol(j)
176            rat_mmol(i) = cmmol(j)/mugaz
177            found = .true.
178            EXIT
179          ENDIF
180        ENDDO
181        IF (.NOT.found) THEN
182          WRITE(*,*) "initracer2:error: "//TRIM(cnames(j))//" is missing from tracers definition file."
183        ENDIF
184      ENDDO
185      IF (n < SIZE(cnames)) THEN
186        WRITE(*,*) "initracer2:error: Inconsistent number of chemical species given (",SIZE(cnames)," expected)"
187        CALL abort_gcm("initracer2", "inconsistent number of tracers", 42)
188      ENDIF
189    ELSE
190      IF (.NOT.ALLOCATED(chimi_indx)) ALLOCATE(chimi_indx(0))
191    ENDIF
192    IF (verb) THEN
193      IF (callmufi.OR.callchim) WRITE(*,*) "===== INITRACER2 SPEAKING ====="
194      IF (callmufi) THEN
195         WRITE(*,*) "Found ",nmicro, "microphysical tracers"
196        call dumpTracers(micro_indx)
197        WRITE(*,*) "-------------------------------"
198      ENDIF
199      IF (callchim) THEN
200        WRITE(*,*) "Found ",nchimi, "chemical tracers"
201        call dumpTracers(chimi_indx)
202        WRITE(*,*) "-------------------------------"
203      ENDIF
204    ENDIF
205
206  END SUBROUTINE initracer2
207
208  FUNCTION indexOfTracer(name, sensitivity) RESULT(idx)
209    !! Get the index of a tracer by name.
210    !!
211    !! The function searches in the global tracer table (tracer_h:noms)
212    !! for the given name and returns the first index matching "name".
213    !!
214    !! If no name in the table matches the given one, -1 is returned !
215    !!
216    !! @warning
217    !! initracers must be called before any use of this function.
218    IMPLICIT NONE
219    CHARACTER(len=*), INTENT(in)  :: name         !! Name of the tracer to search.
220    LOGICAL, OPTIONAL, INTENT(in) :: sensitivity  !! Case sensitivity (true by default).
221    INTEGER :: idx                                !! Index of the first tracer matching name or -1 if not found.
222    LOGICAL                  :: zsens
223    INTEGER                  :: j
224    CHARACTER(len=LEN(name)) :: zname
225    zsens = .true. ; IF(PRESENT(sensitivity)) zsens = sensitivity
226    idx = -1
227    IF (.NOT.ALLOCATED(noms)) RETURN
228    IF (zsens) THEN
229      DO j=1,SIZE(noms)
230        IF (TRIM(noms(j)) == TRIM(name)) THEN
231          idx = j ; RETURN
232        ENDIF
233      ENDDO
234    ELSE
235      zname = to_lower(name)
236      DO j=1,SIZE(noms)
237        IF (TRIM(to_lower(noms(j))) == TRIM(zname)) THEN
238          idx = j ; RETURN
239        ENDIF
240      ENDDO
241    ENDIF
242
243    CONTAINS
244
245    FUNCTION to_lower(istr) RESULT(ostr)
246      !! Lower case conversion function.
247      IMPLICIT NONE
248      CHARACTER(len=*), INTENT(in) :: istr
249      CHARACTER(len=LEN(istr)) :: ostr
250      INTEGER :: i, ic
251      ostr = istr
252      DO i = 1, LEN_TRIM(istr)
253        ic = ICHAR(istr(i:i))
254        IF (ic >= 65 .AND. ic < 90) ostr(i:i) = char(ic + 32)
255      ENDDO
256    END FUNCTION to_lower
257  END FUNCTION indexOfTracer
258
259  FUNCTION nameOfTracer(indx) RESULT(name)
260    !! Get the name of a tracer by index.
261    !!
262    !! The function searches in the global tracer table (tracer_h:noms)
263    !! and returns the name of the tracer at given index.
264    !!
265    !! If the index is out of range an empty string is returned.
266    !!
267    !! @warning
268    !! initracers must be called before any use of this function.
269    IMPLICIT NONE
270    INTEGER, INTENT(in) :: indx   !! Index of the tracer name to retrieve.
271    CHARACTER(len=20)   :: name   !! Name of the tracer at given index.
272    name = ''
273    IF (.NOT.ALLOCATED(noms)) RETURN
274    IF (indx <= 0 .OR. indx > SIZE(noms)) RETURN
275    name = noms(indx)
276  END FUNCTION nameOfTracer
277
278  SUBROUTINE dumpTracers(indexes)
279    !! Print the names of the given list of tracers indexes.
280    INTEGER, DIMENSION(:), INTENT(in) :: indexes
281    INTEGER :: i,idx,nt
282    CHARACTER(len=:), ALLOCATABLE :: suffix
283   
284    IF (.NOT.ALLOCATED(noms)) THEN
285      WRITE(*,'(a)') "[tracers_h:dump_tracers] warning: 'noms' is not allocated, tracers_h:initracer2 has not be called yet"
286      RETURN
287    ENDIF
288    nt = size(noms)
289    WRITE(*,"(a)") "local -> global : name"
290    DO i=1,size(indexes)
291      idx = indexes(i)
292      IF (idx < 1 .OR. idx > nt) THEN
293        ! WRITE(*,'((a),I3,(a),I3,(a))') "index out of range (",idx,"/",nt,")"
294        CYCLE
295      ENDIF
296      IF (ANY(chimi_indx == idx)) THEN
297        suffix = ' (chimi)'
298      ELSE IF (ANY(micro_indx == idx)) THEN
299        suffix = ' (micro'
300        IF (ALLOCATED(ices_indx)) THEN
301          IF (ANY(ices_indx == idx)) suffix=suffix//", ice"
302        ENDIF
303        suffix=suffix//")"
304      ELSE
305        suffix=" ()"
306      ENDIF
307      WRITE(*,'(I5,(a),I6,(a))') i," -> ",idx ," : "//TRIM(noms(i))//suffix
308    ENDDO
309  END SUBROUTINE dumpTracers
310
311
312END MODULE tracer_h
313
Note: See TracBrowser for help on using the repository browser.