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

Last change on this file since 3949 was 3949, checked in by debatzbr, 6 weeks ago

Pluto PCM: Add condensable gas tracers through muphi
BBT

File size: 8.3 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
[3936]14!$OMP THREADPRIVATE(nqtot)
[3184]15
16       logical :: moderntracdef=.false. ! Standard or modern traceur.def
17!$OMP THREADPRIVATE(moderntracdef)
18
[3557]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
[3184]27
28       real,save :: varian      ! Characteristic variance of log-normal distribution
[3557]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)
[3184]31       real,save :: rho_ice     ! Water ice density (kg.m-3)
[3557]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
[3195]38       integer,save :: nmono
[3184]39       real,save :: ref_r0        ! for computing reff=ref_r0*r0 (in log.n. distribution)
[3936]40!$OMP THREADPRIVATE(noms,mmol,aki,cpi,radius,rho_q,qext,qextrhor, &
[3195]41        !$OMP varian,r3n_q,rho_dust,rho_ice,rho_n2,lw_n2,ref_r0)
[3184]42
43       integer, save, allocatable :: is_rad(:)  ! 1 if   ""    ""  in radiative transfer, else 0
[3936]44!$OMP THREADPRIVATE(is_rad)
[3184]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
[3195]54
[3557]55       ! Pluto chemistry
[3195]56       integer,save :: igcm_co_gas
[3184]57       integer,save :: igcm_n2
58       integer,save :: igcm_ar
[3949]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)
[3557]65!$OMP THREADPRIVATE(igcm_co_gas,igcm_n2,igcm_ar,igcm_ch4_gas)
[3949]66!$OMP THREADPRIVATE(igcm_C2H2_mugas,igcm_C2H6_mugas,igcm_C4H2_mugas,igcm_C6H6_mugas,igcm_HCN_mugas)
[3557]67       ! Other tracers
68       integer,save :: igcm_ar_n2   ! for simulations using co2 + neutral gaz
[3195]69       integer,save :: igcm_ch4_ice ! methane ice
[3557]70       integer,save :: igcm_co_ice  ! CO ice
71!$OMP THREADPRIVATE(igcm_ar_n2,igcm_ch4_ice,igcm_co_ice)
[3195]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
[3557]78!$OMP THREADPRIVATE(igcm_prec_haze,igcm_haze,igcm_haze10,igcm_haze30,igcm_haze50,igcm_haze100)
[3195]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
[3557]84!$OMP THREADPRIVATE(igcm_eddy1e6,igcm_eddy1e7,igcm_eddy5e7,igcm_eddy1e8,igcm_eddy5e8)
[3184]85
[3557]86       ! Microphysical model
87       integer, save :: nmicro = 0                 !! Number of microphysics tracers.
88       integer, save, allocatable :: micro_indx(:) !! Indexes of all microphysical tracers
89!$OMP THREADPRIVATE(nmicro)
[3184]90
[3557]91       CONTAINS
[3184]92
[3557]93       FUNCTION indexoftracer(name, sensitivity) RESULT(idx)
94          !! Get the index of a tracer by name.
95          !!
96          !! The function searches in the global tracer table (tracer_h:noms)
97          !! for the given name and returns the first index matching "name".
98          !!
99          !! If no name in the table matches the given one, -1 is returned !
100          IMPLICIT NONE
101          CHARACTER(len=*), INTENT(in)  :: name         !! Name of the tracer to search.
102          LOGICAL, OPTIONAL, INTENT(in) :: sensitivity  !! Case sensitivity (true by default).
103          INTEGER                       :: idx          !! Index of the first tracer matching name or -1 if not found.
104          LOGICAL                       :: zsens
105          INTEGER                       :: j
106          CHARACTER(len=LEN(name))      :: zname
107          zsens = .true. ; IF(PRESENT(sensitivity)) zsens = sensitivity
108          idx = -1
109          IF (.NOT.ALLOCATED(noms)) RETURN
110          IF (zsens) THEN
111             DO j=1,SIZE(noms)
112                IF (TRIM(noms(j)) == TRIM(name)) THEN
113                   idx = j ; RETURN
114                ENDIF
115             ENDDO
116          ELSE
117             zname = to_lower(name)
118             DO j=1,SIZE(noms)
119                IF (TRIM(to_lower(noms(j))) == TRIM(zname)) THEN
120                   idx = j ; RETURN
121                ENDIF
122             ENDDO
123          ENDIF
124
125          CONTAINS
126
127          FUNCTION to_lower(istr) RESULT(ostr)
128             !! Lower case conversion function.
129             IMPLICIT NONE
130             CHARACTER(len=*), INTENT(in) :: istr
131             CHARACTER(len=LEN(istr))     :: ostr
132             INTEGER                      :: i,ic
133             ostr = istr
134             DO i = 1, LEN_TRIM(istr)
135                ic = ICHAR(istr(i:i))
136                IF (ic >= 65 .AND. ic < 90) ostr(i:i) = char(ic + 32)
137             ENDDO
138          END FUNCTION to_lower
139       END FUNCTION indexoftracer
140
141       FUNCTION nameoftracer(indx) RESULT(name)
142          !! Get the name of a tracer by index.
143          !!
144          !! The function searches in the global tracer table (tracer_h:noms)
145          !! and returns the name of the tracer at given index.
146          !!
147          !! If the index is out of range an empty string is returned.
148          IMPLICIT NONE
149          INTEGER, INTENT(in) :: indx   !! Index of the tracer name to retrieve.
150          CHARACTER(len=30)   :: name   !! Name of the tracer at given index.
151          name = ''
152          IF (.NOT.ALLOCATED(noms)) RETURN
153          IF (indx <= 0 .OR. indx > SIZE(noms)) RETURN
154          name = noms(indx)
155       END FUNCTION nameoftracer
156
157       SUBROUTINE dumptracers(indexes)
158          !! Print the names of the given list of tracers indexes.
159          INTEGER, DIMENSION(:), INTENT(in) :: indexes
160          INTEGER :: i,idx
161          CHARACTER(len=:), ALLOCATABLE :: suffix
162
163          IF (.NOT.ALLOCATED(noms)) THEN
164             WRITE(*,'(a)') "[tracers_h:dump_tracers] warning: 'noms' is not allocated, initracer has not be called yet"
165             RETURN
166          ENDIF
167
168          DO i=1,size(indexes)
169             idx = indexes(i)
170             IF (ANY(micro_indx == idx)) THEN
171                suffix = ' (micro)'
172             ELSE
173                suffix=" ()"
174             ENDIF
175             WRITE(*,'(I5,(a),I6,(a))') i," -> ",idx ," : "//TRIM(noms(idx))//suffix
176          ENDDO
177       END SUBROUTINE dumptracers
178
[3936]179       end module tracer_h
Note: See TracBrowser for help on using the repository browser.