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

Last change on this file since 3955 was 3951, checked in by debatzbr, 7 weeks ago

Pluto PCM: Add variables, indices, and flags related to microphysical clouds
BBT

File size: 8.8 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!$OMP THREADPRIVATE(nqtot)
15
16       logical :: moderntracdef=.false. ! Standard or modern traceur.def
17!$OMP THREADPRIVATE(moderntracdef)
18
19       character*30, save, allocatable :: noms(:)! name of the tracer
20       real, save, allocatable :: mmol(:)        ! mole mass of tracer (g/mol)
21       real, save, allocatable :: aki(:)         ! to compute coefficient of thermal concduction if photochem
22       real, save, allocatable :: cpi(:)         ! to compute cpnew in concentration.F if photochem
23       real, save, allocatable :: radius(:)      ! dust and ice particle radius (m)
24       real, save, allocatable :: rho_q(:)       ! tracer densities (kg.m-3)
25       real, save, allocatable :: qext(:)        ! Single Scat. Extinction coeff at 0.67 um
26       real, save, allocatable :: qextrhor(:)    ! Intermediate for computing opt. depth from q
27
28       real,save :: varian      ! Characteristic variance of log-normal distribution
29       real,save :: r3n_q       ! used to compute r0 from number and mass mixing ratio
30       real,save :: rho_dust    ! Mars dust density (kg.m-3)
31       real,save :: rho_ice     ! Water ice density (kg.m-3)
32       real,save :: rho_ch4_ice ! ch4 ice density (kg.m-3)
33       real,save :: rho_co_ice  ! co ice density (kg.m-3)
34       real,save :: rho_n2      ! N2 ice density (kg.m-3)
35       real,save :: lw_ch4      ! Latent heat CH4 gas -> solid
36       real,save :: lw_co       ! Latent heat CO gas -> solid
37       real,save :: lw_n2       ! Latent heat N2 gas -> solid
38       integer,save :: nmono
39       real,save :: ref_r0        ! for computing reff=ref_r0*r0 (in log.n. distribution)
40!$OMP THREADPRIVATE(noms,mmol,aki,cpi,radius,rho_q,qext,qextrhor, &
41        !$OMP varian,r3n_q,rho_dust,rho_ice,rho_n2,lw_n2,ref_r0)
42
43       integer, save, allocatable :: is_rad(:)  ! 1 if   ""    ""  in radiative transfer, else 0
44!$OMP THREADPRIVATE(is_rad)
45
46       integer, save, allocatable :: is_recomb(:)      ! 1 if tracer used in recombining scheme, else 0 (if 1, must have is_rad=1)
47       integer, save, allocatable :: is_recomb_qset(:) ! 1 if tracer k-corr assume predefined vmr, else 0 (if 1, must have is_recomb=1)
48       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)
49!$OMP THREADPRIVATE(is_recomb,is_recomb_qset,is_recomb_qotf)
50       ! Lists of constants for condensable tracers
51
52! tracer indexes: these are initialized in initracer and should be 0 if the
53!                 corresponding tracer does not exist
54
55       ! Pluto chemistry
56       integer,save :: igcm_co_gas
57       integer,save :: igcm_n2
58       integer,save :: igcm_ar
59       integer,save :: igcm_ch4_gas    ! CH4 gas
60       integer,save :: igcm_C2H2_mugas ! C2H2 gas (condensable in microphysics)
61       integer,save :: igcm_C2H6_mugas ! C2H6 gas (condensable in microphysics)
62       integer,save :: igcm_C4H2_mugas ! C4H2 gas (condensable in microphysics)
63       integer,save :: igcm_C6H6_mugas ! C6H6 gas (condensable in microphysics)
64       integer,save :: igcm_HCN_mugas  ! HCN gas  (condensable in microphysics)
65!$OMP THREADPRIVATE(igcm_co_gas,igcm_n2,igcm_ar,igcm_ch4_gas)
66!$OMP THREADPRIVATE(igcm_C2H2_mugas,igcm_C2H6_mugas,igcm_C4H2_mugas,igcm_C6H6_mugas,igcm_HCN_mugas)
67       ! Other tracers
68       integer,save :: igcm_ar_n2   ! for simulations using co2 + neutral gaz
69       integer,save :: igcm_ch4_ice ! methane ice
70       integer,save :: igcm_co_ice  ! CO ice
71!$OMP THREADPRIVATE(igcm_ar_n2,igcm_ch4_ice,igcm_co_ice)
72       integer,save :: igcm_prec_haze
73       integer,save :: igcm_haze
74       integer,save :: igcm_haze10
75       integer,save :: igcm_haze30
76       integer,save :: igcm_haze50
77       integer,save :: igcm_haze100
78!$OMP THREADPRIVATE(igcm_prec_haze,igcm_haze,igcm_haze10,igcm_haze30,igcm_haze50,igcm_haze100)
79       integer,save :: igcm_eddy1e6
80       integer,save :: igcm_eddy1e7
81       integer,save :: igcm_eddy5e7
82       integer,save :: igcm_eddy1e8
83       integer,save :: igcm_eddy5e8
84!$OMP THREADPRIVATE(igcm_eddy1e6,igcm_eddy1e7,igcm_eddy5e7,igcm_eddy1e8,igcm_eddy5e8)
85
86       ! Microphysical haze model related
87       integer, save :: nmicro = 0                 ! Number of microphysics tracers.
88       integer, save, allocatable :: micro_indx(:) ! Indexes of all microphysical tracers
89!$OMP THREADPRIVATE(nmicro,micro_indx)
90       ! Microphysical cloud model related
91       integer, save :: nmicro_ices = 0                ! Number of microphysics ice tracers (subset of nmicro).
92       integer, save, allocatable :: micro_ice_indx(:) ! Indexes of microphysical ice tracers
93       integer, save, allocatable :: micro_gas_indx(:) ! Indexes of microphysical gas tracers
94!$OMP THREADPRIVATE(nmicro_ices,micro_ice_indx,micro_gas_indx)
95
96       CONTAINS
97
98       FUNCTION indexoftracer(name, sensitivity) RESULT(idx)
99          !! Get the index of a tracer by name.
100          !!
101          !! The function searches in the global tracer table (tracer_h:noms)
102          !! for the given name and returns the first index matching "name".
103          !!
104          !! If no name in the table matches the given one, -1 is returned !
105          IMPLICIT NONE
106          CHARACTER(len=*), INTENT(in)  :: name         !! Name of the tracer to search.
107          LOGICAL, OPTIONAL, INTENT(in) :: sensitivity  !! Case sensitivity (true by default).
108          INTEGER                       :: idx          !! Index of the first tracer matching name or -1 if not found.
109          LOGICAL                       :: zsens
110          INTEGER                       :: j
111          CHARACTER(len=LEN(name))      :: zname
112          zsens = .true. ; IF(PRESENT(sensitivity)) zsens = sensitivity
113          idx = -1
114          IF (.NOT.ALLOCATED(noms)) RETURN
115          IF (zsens) THEN
116             DO j=1,SIZE(noms)
117                IF (TRIM(noms(j)) == TRIM(name)) THEN
118                   idx = j ; RETURN
119                ENDIF
120             ENDDO
121          ELSE
122             zname = to_lower(name)
123             DO j=1,SIZE(noms)
124                IF (TRIM(to_lower(noms(j))) == TRIM(zname)) THEN
125                   idx = j ; RETURN
126                ENDIF
127             ENDDO
128          ENDIF
129
130          CONTAINS
131
132          FUNCTION to_lower(istr) RESULT(ostr)
133             !! Lower case conversion function.
134             IMPLICIT NONE
135             CHARACTER(len=*), INTENT(in) :: istr
136             CHARACTER(len=LEN(istr))     :: ostr
137             INTEGER                      :: i,ic
138             ostr = istr
139             DO i = 1, LEN_TRIM(istr)
140                ic = ICHAR(istr(i:i))
141                IF (ic >= 65 .AND. ic < 90) ostr(i:i) = char(ic + 32)
142             ENDDO
143          END FUNCTION to_lower
144       END FUNCTION indexoftracer
145
146       FUNCTION nameoftracer(indx) RESULT(name)
147          !! Get the name of a tracer by index.
148          !!
149          !! The function searches in the global tracer table (tracer_h:noms)
150          !! and returns the name of the tracer at given index.
151          !!
152          !! If the index is out of range an empty string is returned.
153          IMPLICIT NONE
154          INTEGER, INTENT(in) :: indx   !! Index of the tracer name to retrieve.
155          CHARACTER(len=30)   :: name   !! Name of the tracer at given index.
156          name = ''
157          IF (.NOT.ALLOCATED(noms)) RETURN
158          IF (indx <= 0 .OR. indx > SIZE(noms)) RETURN
159          name = noms(indx)
160       END FUNCTION nameoftracer
161
162       SUBROUTINE dumptracers(indexes)
163          !! Print the names of the given list of tracers indexes.
164          INTEGER, DIMENSION(:), INTENT(in) :: indexes
165          INTEGER :: i,idx
166          CHARACTER(len=:), ALLOCATABLE :: suffix
167
168          IF (.NOT.ALLOCATED(noms)) THEN
169             WRITE(*,'(a)') "[tracers_h:dump_tracers] warning: 'noms' is not allocated, initracer has not be called yet"
170             RETURN
171          ENDIF
172
173          WRITE(*,"(a)") "local -> global : name"
174
175          DO i=1,size(indexes)
176             idx = indexes(i)
177             IF (ANY(micro_indx == idx)) THEN
178                suffix = ' (micro)'
179             ELSE
180                suffix=" ()"
181             ENDIF
182             WRITE(*,'(I5,(a),I6,(a))') i," -> ",idx ," : "//TRIM(noms(idx))//suffix
183          ENDDO
184       END SUBROUTINE dumptracers
185
186       end module tracer_h
Note: See TracBrowser for help on using the repository browser.