GCC Code Coverage Report


Directory: ./
File: dyn3d_common/infotrac.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 192 387 49.6%
Branches: 210 476 44.1%

Line Branch Exec Source
1 ! $Id: infotrac.F90 3998 2021-11-02 14:54:30Z emillour $
2 !
3 MODULE infotrac
4
5 ! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
6 INTEGER, SAVE :: nqtot
7 !CR: on ajoute le nombre de traceurs de l eau
8 INTEGER, SAVE :: nqo
9
10 ! nbtr : number of tracers not including higher order of moment or water vapor or liquid
11 ! number of tracers used in the physics
12 INTEGER, SAVE :: nbtr
13
14 ! CRisi: on retranche les isotopes des traceurs habituels
15 ! On fait un tableaux d'indices des traceurs qui passeront dans phytrac
16 INTEGER, SAVE :: nqtottr
17 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: itr_indice
18
19 ! CRisi: nb traceurs peres= directement advectes par l'air
20 INTEGER, SAVE :: nqperes
21
22 ! ThL: nb traceurs INCA
23 INTEGER, SAVE :: nqINCA
24
25 ! ThL: nb traceurs CO2
26 INTEGER, SAVE :: nqCO2
27
28 ! Name variables
29 CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
30 CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
31
32 ! iadv : index of trasport schema for each tracer
33 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iadv
34
35 ! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
36 ! dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
37 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: niadv ! equivalent dyn / physique
38
39 ! CRisi: tableaux de fils
40 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: nqfils
41 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: nqdesc ! nombres de fils + nombre de tous les petits fils sur toutes les generations
42 INTEGER, SAVE :: nqdesc_tot
43 INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: iqfils
44 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iqpere
45 REAL :: qperemin,masseqmin,ratiomin ! MVals et CRisi
46 PARAMETER (qperemin=1e-16,masseqmin=1e-16,ratiomin=1e-16) ! MVals
47
48 ! conv_flg(it)=0 : convection desactivated for tracer number it
49 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: conv_flg
50 ! pbl_flg(it)=0 : boundary layer diffusion desactivaded for tracer number it
51 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: pbl_flg
52
53 CHARACTER(len=4),SAVE :: type_trac
54 CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
55
56 ! CRisi: cas particulier des isotopes
57 LOGICAL,SAVE :: ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso
58 INTEGER :: niso_possibles
59 PARAMETER ( niso_possibles=5)
60 REAL, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
61 LOGICAL, DIMENSION(niso_possibles),SAVE :: use_iso
62 INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: iqiso ! donne indice iq en fn de (ixt,phase)
63 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iso_num ! donne numero iso entre 1 et niso_possibles en fn de nqtot
64 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iso_indnum ! donne numero iso entre 1 et niso effectif en fn de nqtot
65 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: zone_num ! donne numero de la zone de tracage en fn de nqtot
66 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: phase_num ! donne numero de la zone de tracage en fn de nqtot
67 INTEGER, DIMENSION(niso_possibles), SAVE :: indnum_fn_num ! donne indice entre entre 1 et niso en fonction du numero d isotope entre 1 et niso_possibles
68 INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: index_trac ! numero ixt en fn izone, indnum entre 1 et niso
69 INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso
70
71
72 CONTAINS
73
74 1 SUBROUTINE infotrac_init
75 USE control_mod, ONLY: planet_type, config_inca
76 IMPLICIT NONE
77 !=======================================================================
78 !
79 ! Auteur: P. Le Van /L. Fairhead/F.Hourdin
80 ! -------
81 ! Modif special traceur F.Forget 05/94
82 ! Modif M-A Filiberti 02/02 lecture de traceur.def
83 !
84 ! Objet:
85 ! ------
86 ! GCM LMD nouvelle grille
87 !
88 !=======================================================================
89 ! ... modification de l'integration de q ( 26/04/94 ) ....
90 !-----------------------------------------------------------------------
91 ! Declarations
92
93 INCLUDE "dimensions.h"
94 INCLUDE "iniprint.h"
95
96 ! Local variables
97 INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv ! index of horizontal trasport schema
98 INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv ! index of vertical trasport schema
99
100 INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv_inca ! index of horizontal trasport schema
101 INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv_inca ! index of vertical trasport schema
102
103 INTEGER, ALLOCATABLE, DIMENSION(:) :: conv_flg_inca
104 INTEGER, ALLOCATABLE, DIMENSION(:) :: pbl_flg_inca
105 CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: solsym_inca
106
107 CHARACTER(len=30), ALLOCATABLE, DIMENSION(:) :: tnom_0 ! tracer short name
108 CHARACTER(len=30), ALLOCATABLE, DIMENSION(:) :: tnom_transp ! transporting fluid short name: CRisi
109 CHARACTER(len=3), DIMENSION(30) :: descrq
110 CHARACTER(len=1), DIMENSION(3) :: txts
111 CHARACTER(len=2), DIMENSION(9) :: txtp
112 CHARACTER(len=23) :: str1,str2
113
114 INTEGER :: nqtrue ! number of tracers read from tracer.def, without higer order of moment
115 INTEGER :: iq, new_iq, iiq, jq, ierr,itr
116 INTEGER :: ifils,ipere,generation ! CRisi
117 LOGICAL :: continu,nouveau_traceurdef
118 INTEGER :: IOstatus ! gestion de la retrocompatibilite de traceur.def
119 CHARACTER(len=30) :: tchaine
120
121 character(len=*),parameter :: modname="infotrac_init"
122
123 !-----------------------------------------------------------------------
124 ! Initialization :
125 !
126
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 txts=(/'x','y','z'/)
127
2/2
✓ Branch 0 taken 9 times.
✓ Branch 1 taken 1 times.
10 txtp=(/'x ','y ','z ','xx','xy','xz','yy','yz','zz'/)
128
129 1 descrq(14)='VLH'
130 1 descrq(10)='VL1'
131 1 descrq(11)='VLP'
132 1 descrq(12)='FH1'
133 1 descrq(13)='FH2'
134 1 descrq(16)='PPM'
135 1 descrq(17)='PPS'
136 1 descrq(18)='PPP'
137 1 descrq(20)='SLP'
138 1 descrq(30)='PRA'
139
140
141 ! Coherence test between parameter type_trac, config_inca and preprocessing keys
142
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (type_trac=='inca') THEN
143 WRITE(lunout,*) 'You have chosen to couple with INCA chemistry model : type_trac=', &
144 type_trac,' config_inca=',config_inca
145 IF (config_inca/='aero' .AND. config_inca/='aeNP' .AND. config_inca/='chem') THEN
146 WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
147 CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
148 ENDIF
149 WRITE(lunout,*) 'To run this option you must add cpp key INCA and compile with INCA code'
150 CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
151
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 ELSE IF (type_trac=='repr') THEN
152 WRITE(lunout,*) 'You have chosen to couple with REPROBUS chemestry model : type_trac=', type_trac
153 WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
154 CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
155
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 ELSE IF (type_trac == 'co2i') THEN
156 WRITE(lunout,*) 'You have chosen to run with CO2 cycle: type_trac=', type_trac
157
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 ELSE IF (type_trac == 'coag') THEN
158 WRITE(lunout,*) 'Tracers are treated for COAGULATION tests : type_trac=', type_trac
159 WRITE(lunout,*) 'To run this option you must add cpp key StratAer and compile with StratAer code'
160 CALL abort_gcm('infotrac_init','You must compile with cpp key StratAer',1)
161
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 ELSE IF (type_trac == 'lmdz') THEN
162 1 WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
163 ELSE IF (type_trac == 'inco') THEN ! ThL
164 WRITE(lunout,*) 'Using jointly INCA and CO2 cycle: type_trac =', type_trac
165 IF (config_inca/='aero' .AND. config_inca/='aeNP' .AND. config_inca/='chem') THEN
166 WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
167 CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
168 ENDIF
169 WRITE(lunout,*) 'To run this option you must add cpp key INCA and compilewith INCA code'
170 CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
171 ELSE
172 WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
173 CALL abort_gcm('infotrac_init','bad parameter',1)
174 ENDIF
175
176 ! Test if config_inca is other then none for run without INCA
177
3/6
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
1 IF (type_trac/='inca' .AND. type_trac/='inco' .AND. config_inca/='none') THEN
178 WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
179 config_inca='none'
180 ENDIF
181
182 !-----------------------------------------------------------------------
183 !
184 ! 1) Get the true number of tracers + water vapor/liquid
185 ! Here true tracers (nqtrue) means declared tracers (only first order)
186 !
187 !-----------------------------------------------------------------------
188
1/8
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
1 IF (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac == 'coag' .OR. type_trac == 'co2i') THEN
189
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (type_trac=='co2i') THEN
190 nqCO2 = 1
191 ELSE
192 1 nqCO2 = 0
193 ENDIF
194 1 OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
195
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF(ierr.EQ.0) THEN
196 1 WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
197 1 READ(90,*) nqtrue
198 1 write(lunout,*) 'nqtrue=',nqtrue
199 ELSE
200 WRITE(lunout,*) trim(modname),': Failed opening traceur.def'
201 CALL abort_gcm(modname,"file traceur.def not found!",1)
202 ENDIF
203 !jyg<
204 !! if ( planet_type=='earth') then
205 !! ! For Earth, water vapour & liquid tracers are not in the physics
206 !! nbtr=nqtrue-2
207 !! else
208 !! ! Other planets (for now); we have the same number of tracers
209 !! ! in the dynamics than in the physics
210 !! nbtr=nqtrue
211 !! endif
212 !>jyg
213 ELSE ! type_trac=inca or inco
214 IF (type_trac=='inco') THEN
215 nqCO2 = 1
216 ELSE
217 nqCO2 = 0
218 ENDIF
219 !jyg<
220 ! The traceur.def file is used to define the number "nqo" of water phases
221 ! present in the simulation. Default : nqo = 2.
222 OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
223 IF(ierr.EQ.0) THEN
224 WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
225 READ(90,*) nqo
226 ELSE
227 WRITE(lunout,*) trim(modname),': Failed opening traceur.def'
228 CALL abort_gcm(modname,"file traceur.def not found!",1)
229 ENDIF
230 IF (nqo /= 2 .AND. nqo /= 3 ) THEN
231 IF (nqo == 4 .AND. type_trac=='inco') THEN ! ThL
232 WRITE(lunout,*) trim(modname),': you are coupling with INCA, and also using CO2i.'
233 nqo = 3 ! A ameliorier... je force 3 traceurs eau... ThL
234 WRITE(lunout,*) trim(modname),': nqo = ',nqo
235 ELSE
236 WRITE(lunout,*) trim(modname),': nqo=',nqo, ' is not allowed. Only 2 or 3 water phases allowed'
237 CALL abort_gcm('infotrac_init','Bad number of water phases',1)
238 ENDIF
239 ENDIF
240 ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
241 nqINCA=0
242 nbtr=nqINCA+nqCO2
243 nqtrue=nbtr+nqo
244 WRITE(lunout,*) trim(modname),': nqo = ',nqo
245 WRITE(lunout,*) trim(modname),': nbtr = ',nbtr
246 WRITE(lunout,*) trim(modname),': nqtrue = ',nqtrue
247 WRITE(lunout,*) trim(modname),': nqCO2 = ',nqCO2
248 WRITE(lunout,*) trim(modname),': nqINCA = ',nqINCA
249 ALLOCATE(hadv_inca(nqINCA), vadv_inca(nqINCA), conv_flg_inca(nqINCA), pbl_flg_inca(nqINCA), solsym_inca(nqINCA))
250 ENDIF ! type_trac 'inca' ou 'inco'
251 !>jyg
252
253
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
1 IF ((planet_type=="earth").and.(nqtrue < 2)) THEN
254 WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowed. 2 tracers is the minimum'
255 CALL abort_gcm('infotrac_init','Not enough tracers',1)
256 ENDIF
257
258 !jyg<
259
260 !
261 ! Allocate variables depending on nqtrue
262 !
263
6/12
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 1 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 1 times.
1 ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue),tnom_transp(nqtrue))
264
265
266 !-----------------------------------------------------------------------
267 ! 2) Choix des schemas d'advection pour l'eau et les traceurs
268 !
269 ! iadv = 1 schema transport type "humidite specifique LMD"
270 ! iadv = 2 schema amont
271 ! iadv = 14 schema Van-leer + humidite specifique
272 ! Modif F.Codron
273 ! iadv = 10 schema Van-leer (retenu pour l'eau vapeur et liquide)
274 ! iadv = 11 schema Van-Leer pour hadv et version PPM (Monotone) pour vadv
275 ! iadv = 12 schema Frederic Hourdin I
276 ! iadv = 13 schema Frederic Hourdin II
277 ! iadv = 16 schema PPM Monotone(Collela & Woodward 1984)
278 ! iadv = 17 schema PPM Semi Monotone (overshoots autorises)
279 ! iadv = 18 schema PPM Positif Defini (overshoots undershoots autorises)
280 ! iadv = 20 schema Slopes
281 ! iadv = 30 schema Prather
282 !
283 ! Dans le tableau q(ij,l,iq) : iq = 1 pour l'eau vapeur
284 ! iq = 2 pour l'eau liquide
285 ! Et eventuellement iq = 3,nqtot pour les autres traceurs
286 !
287 ! iadv(1): choix pour l'eau vap. et iadv(2) : choix pour l'eau liq.
288 !------------------------------------------------------------------------
289 !
290 ! Get choice of advection schema from file tracer.def or from INCA
291 !---------------------------------------------------------------------
292
1/8
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
1 IF (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac == 'coag' .OR. type_trac == 'co2i') THEN
293
294 ! Continue to read tracer.def
295
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 DO iq=1,nqtrue
296
297 5 write(*,*) 'infotrac 237: iq=',iq
298 ! CRisi: ajout du nom du fluide transporteur
299 ! mais rester retro compatible
300 5 READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine
301 5 write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq)
302 5 write(lunout,*) 'tchaine=',trim(tchaine)
303 5 write(*,*) 'infotrac 238: IOstatus=',IOstatus
304
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
5 if (IOstatus.ne.0) then
305 CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1)
306 endif
307 ! Y-a-t-il 1 ou 2 noms de traceurs? -> On regarde s'il y a un
308 ! espace ou pas au milieu de la chaine.
309 continu=.true.
310 5 nouveau_traceurdef=.false.
311 5 iiq=1
312 do while (continu)
313
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 16 times.
16 if (tchaine(iiq:iiq).eq.' ') then
314 nouveau_traceurdef=.true.
315 continu=.false.
316
2/2
✓ Branch 0 taken 11 times.
✓ Branch 1 taken 5 times.
16 else if (iiq.lt.LEN_TRIM(tchaine)) then
317 11 iiq=iiq+1
318 else
319 continu=.false.
320 endif
321 enddo
322 5 write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef
323
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
5 if (nouveau_traceurdef) then
324 write(lunout,*) 'C''est la nouvelle version de traceur.def'
325 tnom_0(iq)=tchaine(1:iiq-1)
326 tnom_transp(iq)=tchaine(iiq+1:30)
327 else
328 5 write(lunout,*) 'C''est l''ancienne version de traceur.def'
329 5 write(lunout,*) 'On suppose que les traceurs sont tous d''air'
330 5 tnom_0(iq)=tchaine
331 5 tnom_transp(iq) = 'air'
332 endif
333
1/2
✓ Branch 3 taken 5 times.
✗ Branch 4 not taken.
5 write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>'
334
1/2
✓ Branch 3 taken 5 times.
✗ Branch 4 not taken.
6 write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
335
336 ENDDO!DO iq=1,nqtrue
337
338 1 CLOSE(90)
339
340 1 WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
341 1 WRITE(lunout,*) trim(modname),': nombre total de traceurs ',nqtrue
342
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 DO iq=1,nqtrue
343 6 WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq),tnom_transp(iq)
344 END DO
345
346
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF ( planet_type=='earth') THEN
347 !CR: nombre de traceurs de l eau
348
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (tnom_0(3) == 'H2Oi') THEN
349 1 nqo=3
350 ELSE
351 nqo=2
352 ENDIF
353 ! For Earth, water vapour & liquid tracers are not in the physics
354 1 nbtr=nqtrue-nqo
355 ELSE
356 ! Other planets (for now); we have the same number of tracers
357 ! in the dynamics than in the physics
358 nbtr=nqtrue
359 ENDIF
360
361
362 ENDIF ! (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac = 'coag' .OR. type_trac = 'co2i')
363 !jyg<
364 !
365
366 ! Transfert number of tracers to Reprobus
367 IF (type_trac == 'repr') THEN
368 ENDIF
369 !
370 ! Allocate variables depending on nbtr
371 !
372
8/16
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✓ Branch 14 taken 1 times.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✓ Branch 17 taken 1 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 1 times.
1 ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
373
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 conv_flg(:) = 1 ! convection activated for all tracers
374
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 pbl_flg(:) = 1 ! boundary layer activated for all tracers
375
376
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
1 IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN ! config_inca='aero' ou 'chem'
377 !>jyg
378 ! le module de chimie fournit les noms des traceurs
379 ! et les schemas d'advection associes. excepte pour ceux lus
380 ! dans traceur.def
381
382 DO iq=1,nqo+nqCO2
383
384 write(*,*) 'infotrac 237: iq=',iq
385 ! CRisi: ajout du nom du fluide transporteur
386 ! mais rester retro compatible
387 READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine
388 write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq)
389 write(lunout,*) 'tchaine=',trim(tchaine)
390 write(*,*) 'infotrac 238: IOstatus=',IOstatus
391 if (IOstatus.ne.0) then
392 CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1)
393 endif
394 ! Y-a-t-il 1 ou 2 noms de traceurs? -> On regarde s'il y a un
395 ! espace ou pas au milieu de la chaine.
396 continu=.true.
397 nouveau_traceurdef=.false.
398 iiq=1
399
400 do while (continu)
401 if (tchaine(iiq:iiq).eq.' ') then
402 nouveau_traceurdef=.true.
403 continu=.false.
404 else if (iiq.lt.LEN_TRIM(tchaine)) then
405 iiq=iiq+1
406 else
407 continu=.false.
408 endif
409 enddo
410
411 write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef
412
413 if (nouveau_traceurdef) then
414 write(lunout,*) 'C''est la nouvelle version de traceur.def'
415 tnom_0(iq)=tchaine(1:iiq-1)
416 tnom_transp(iq)=tchaine(iiq+1:30)
417 else
418 write(lunout,*) 'C''est l''ancienne version de traceur.def'
419 write(lunout,*) 'On suppose que les traceurs sont tous d''air'
420 tnom_0(iq)=tchaine
421 tnom_transp(iq) = 'air'
422 endif
423
424 write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>'
425 write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
426
427 ENDDO !DO iq=1,nqo
428 CLOSE(90)
429
430
431
432 !jyg<
433 DO iq = nqo+nqCO2+1, nqtrue
434 hadv(iq) = hadv_inca(iq-nqo-nqCO2)
435 vadv(iq) = vadv_inca(iq-nqo-nqCO2)
436 tnom_0(iq)=solsym_inca(iq-nqo-nqCO2)
437 1 tnom_transp(iq) = 'air'
438 END DO
439
440 ENDIF ! (type_trac == 'inca' or 'inco')
441
442 !-----------------------------------------------------------------------
443 !
444 ! 3) Verify if advection schema 20 or 30 choosen
445 ! Calculate total number of tracers needed: nqtot
446 ! Allocate variables depending on total number of tracers
447 !-----------------------------------------------------------------------
448 new_iq=0
449
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 DO iq=1,nqtrue
450 ! Add tracers for certain advection schema
451
2/4
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 5 times.
✗ Branch 3 not taken.
6 IF (hadv(iq)<20 .AND. vadv(iq)<20 ) THEN
452 5 new_iq=new_iq+1 ! no tracers added
453 ELSE IF (hadv(iq)==20 .AND. vadv(iq)==20 ) THEN
454 new_iq=new_iq+4 ! 3 tracers added
455 ELSE IF (hadv(iq)==30 .AND. vadv(iq)==30 ) THEN
456 new_iq=new_iq+10 ! 9 tracers added
457 ELSE
458 WRITE(lunout,*) trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
459 CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1)
460 ENDIF
461 END DO
462
463
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (new_iq /= nqtrue) THEN
464 ! The choice of advection schema imposes more tracers
465 ! Assigne total number of tracers
466 nqtot = new_iq
467
468 WRITE(lunout,*) trim(modname),': The choice of advection schema for one or more tracers'
469 WRITE(lunout,*) 'makes it necessary to add tracers'
470 WRITE(lunout,*) trim(modname)//': ',nqtrue,' is the number of true tracers'
471 WRITE(lunout,*) trim(modname)//': ',nqtot, ' is the total number of tracers needed'
472
473 ELSE
474 ! The true number of tracers is also the total number
475 1 nqtot = nqtrue
476 ENDIF
477
478 !
479 ! Allocate variables with total number of tracers, nqtot
480 !
481
6/12
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✓ Branch 8 taken 1 times.
✗ Branch 9 not taken.
✗ Branch 10 not taken.
✓ Branch 11 taken 1 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 1 times.
1 ALLOCATE(tname(nqtot), ttext(nqtot))
482
5/10
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
1 ALLOCATE(iadv(nqtot), niadv(nqtot))
483
484 !-----------------------------------------------------------------------
485 !
486 ! 4) Determine iadv, long and short name
487 !
488 !-----------------------------------------------------------------------
489 new_iq=0
490
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 DO iq=1,nqtrue
491 5 new_iq=new_iq+1
492
493 ! Verify choice of advection schema
494
1/2
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
5 IF (hadv(iq)==vadv(iq)) THEN
495 5 iadv(new_iq)=hadv(iq)
496 ELSE IF (hadv(iq)==10 .AND. vadv(iq)==16) THEN
497 iadv(new_iq)=11
498 ELSE
499 WRITE(lunout,*)trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
500
501 CALL abort_gcm('infotrac_init','Bad choice of advection schema - 2',1)
502 ENDIF
503
504 5 str1=tnom_0(iq)
505 5 tname(new_iq)= tnom_0(iq)
506
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
5 IF (iadv(new_iq)==0) THEN
507 ttext(new_iq)=trim(str1)
508 ELSE
509
2/4
✓ Branch 2 taken 5 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 5 times.
✗ Branch 5 not taken.
5 ttext(new_iq)=trim(tnom_0(iq))//descrq(iadv(new_iq))
510 ENDIF
511
512 ! schemas tenant compte des moments d'ordre superieur
513 5 str2=ttext(new_iq)
514
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
6 IF (iadv(new_iq)==20) THEN
515 DO jq=1,3
516 new_iq=new_iq+1
517 iadv(new_iq)=-20
518 ttext(new_iq)=trim(str2)//txts(jq)
519 tname(new_iq)=trim(str1)//txts(jq)
520 END DO
521
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
5 ELSE IF (iadv(new_iq)==30) THEN
522 DO jq=1,9
523 new_iq=new_iq+1
524 iadv(new_iq)=-30
525 ttext(new_iq)=trim(str2)//txtp(jq)
526 tname(new_iq)=trim(str1)//txtp(jq)
527 END DO
528 ENDIF
529 END DO
530
531 !
532 ! Find vector keeping the correspodence between true and total tracers
533 !
534
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 niadv(:)=0
535 1 iiq=0
536
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 DO iq=1,nqtot
537
1/2
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
6 IF(iadv(iq).GE.0) THEN
538 ! True tracer
539 5 iiq=iiq+1
540 5 niadv(iiq)=iq
541 ENDIF
542 END DO
543
544
545 1 WRITE(lunout,*) trim(modname),': Information stored in infotrac :'
546 1 WRITE(lunout,*) trim(modname),': iadv niadv tname ttext :'
547
548
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 DO iq=1,nqtot
549
2/4
✓ Branch 5 taken 5 times.
✗ Branch 6 not taken.
✓ Branch 10 taken 5 times.
✗ Branch 11 not taken.
6 WRITE(lunout,*) iadv(iq),niadv(iq), ' ',trim(tname(iq)),' ',trim(ttext(iq))
550 END DO
551
552 !
553 ! Test for advection schema.
554 ! This version of LMDZ only garantees iadv=10 and iadv=14 (14 only for water vapour) .
555 !
556
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 DO iq=1,nqtot
557
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
6 IF (iadv(iq)/=10 .AND. iadv(iq)/=14 .AND. iadv(iq)/=0) THEN
558 WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
559 CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1)
560
3/4
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 4 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
5 ELSE IF (iadv(iq)==14 .AND. iq/=1) THEN
561 WRITE(lunout,*)trim(modname),'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
562 CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1)
563 ENDIF
564 END DO
565
566
567 ! CRisi: quels sont les traceurs fils et les traceurs peres.
568 ! initialiser tous les tableaux d'indices lies aux traceurs familiaux
569 ! + verifier que tous les peres sont ecrits en premieres positions
570
5/10
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
1 ALLOCATE(nqfils(nqtot),nqdesc(nqtot))
571
3/6
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
1 ALLOCATE(iqfils(nqtot,nqtot))
572
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(iqpere(nqtot))
573 1 nqperes=0
574
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 nqfils(:)=0
575
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 nqdesc(:)=0
576
4/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 25 times.
✓ Branch 3 taken 5 times.
31 iqfils(:,:)=0
577
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 iqpere(:)=0
578 1 nqdesc_tot=0
579
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 DO iq=1,nqtot
580
1/2
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
6 if (tnom_transp(iq) == 'air') then
581 ! ceci est un traceur pere
582
1/2
✓ Branch 5 taken 5 times.
✗ Branch 6 not taken.
5 WRITE(lunout,*) 'Le traceur',iq,', appele ',trim(tnom_0(iq)),', est un pere'
583 5 nqperes=nqperes+1
584 5 iqpere(iq)=0
585 else !if (tnom_transp(iq) == 'air') then
586 ! ceci est un fils. Qui est son pere?
587 WRITE(lunout,*) 'Le traceur',iq,', appele ',trim(tnom_0(iq)),', est un fils'
588 continu=.true.
589 ipere=1
590 do while (continu)
591 if (tnom_transp(iq) == tnom_0(ipere)) then
592 ! Son pere est ipere
593 WRITE(lunout,*) 'Le traceur',iq,'appele ', &
594 & trim(tnom_0(iq)),' est le fils de ',ipere,'appele ',trim(tnom_0(ipere))
595 if (iq.eq.ipere) then
596 CALL abort_gcm('infotrac_init','Un fils est son propre pere',1)
597 endif
598 nqfils(ipere)=nqfils(ipere)+1
599 iqfils(nqfils(ipere),ipere)=iq
600 iqpere(iq)=ipere
601 continu=.false.
602 else !if (tnom_transp(iq) == tnom_0(ipere)) then
603 ipere=ipere+1
604 if (ipere.gt.nqtot) then
605 WRITE(lunout,*) 'Le traceur',iq,'appele ', &
606 & trim(tnom_0(iq)),', est orphelin.'
607 CALL abort_gcm('infotrac_init','Un traceur est orphelin',1)
608 endif !if (ipere.gt.nqtot) then
609 endif !if (tnom_transp(iq) == tnom_0(ipere)) then
610 enddo !do while (continu)
611 endif !if (tnom_transp(iq) == 'air') then
612 enddo !DO iq=1,nqtot
613 1 WRITE(lunout,*) 'infotrac: nqperes=',nqperes
614 1 WRITE(lunout,*) 'nqfils=',nqfils
615 1 WRITE(lunout,*) 'iqpere=',iqpere
616 1 WRITE(lunout,*) 'iqfils=',iqfils
617
618 ! Calculer le nombre de descendants a partir de iqfils et de nbfils
619
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 DO iq=1,nqtot
620 5 generation=0
621 continu=.true.
622 ifils=iq
623
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 5 times.
10 do while (continu)
624 5 ipere=iqpere(ifils)
625
1/2
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
5 if (ipere.gt.0) then
626 nqdesc(ipere)=nqdesc(ipere)+1
627 nqdesc_tot=nqdesc_tot+1
628 iqfils(nqdesc(ipere),ipere)=iq
629 ifils=ipere
630 generation=generation+1
631 else !if (ipere.gt.0) then
632 continu=.false.
633 endif !if (ipere.gt.0) then
634 enddo !do while (continu)
635
1/2
✓ Branch 5 taken 5 times.
✗ Branch 6 not taken.
6 WRITE(lunout,*) 'Le traceur ',iq,', appele ',trim(tnom_0(iq)),' est un traceur de generation: ',generation
636 enddo !DO iq=1,nqtot
637 1 WRITE(lunout,*) 'infotrac: nqdesc=',nqdesc
638 1 WRITE(lunout,*) 'iqfils=',iqfils
639 1 WRITE(lunout,*) 'nqdesc_tot=',nqdesc_tot
640
641 ! Interdire autres schemas que 10 pour les traceurs fils, et autres schemas
642 ! que 10 et 14 si des peres ont des fils
643
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 do iq=1,nqtot
644
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
6 if (iqpere(iq).gt.0) then
645 ! ce traceur a un pere qui n'est pas l'air
646 ! Seul le schema 10 est autorise
647 if (iadv(iq)/=10) then
648 WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not implemented for sons'
649 CALL abort_gcm('infotrac_init','Sons should be advected by scheme 10',1)
650 endif
651 ! Le traceur pere ne peut etre advecte que par schema 10 ou 14:
652 IF (iadv(iqpere(iq))/=10 .AND. iadv(iqpere(iq))/=14) THEN
653 WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not implemented for fathers'
654 CALL abort_gcm('infotrac_init','Fathers should be advected by scheme 10 ou 14',1)
655 endif !IF (iadv(iqpere(iq))/=10 .AND. iadv(iqpere(iq))/=14) THEN
656 endif !if (iqpere(iq).gt.0) the
657 enddo !do iq=1,nqtot
658
659
660
661 ! detecter quels sont les traceurs isotopiques parmi des traceurs
662 1 call infotrac_isoinit(tnom_0,nqtrue)
663
664 ! if (ntraciso.gt.0) then
665 ! le 18 sep 2020: on enleve la condition ntraciso.gt.0 car nqtottr doit etre
666 ! connu meme si il n'y a pas d'isotopes!
667 1 write(lunout,*) 'infotrac 702: nbtr,ntraciso=',nbtr,ntraciso
668 ! retrancher les traceurs isotopiques de la liste des traceurs qui passent dans
669 ! phytrac
670 1 nbtr=nbtr-nqo*ntraciso
671
672 ! faire un tableau d'indice des traceurs qui passeront dans phytrac
673 1 nqtottr=nqtot-nqo*(1+ntraciso)
674 1 write(lunout,*) 'infotrac 704: nqtottr,nqtot,nqo=',nqtottr,nqtot,nqo
675 ! Rq: nqtottr n'est pas forcement egal a nbtr dans le cas ou new_iq /= nqtrue
676
3/6
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
1 ALLOCATE (itr_indice(nqtottr))
677
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 itr_indice(:)=0
678 1 itr=0
679
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 do iq=nqo+1, nqtot
680
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
3 if (iso_num(iq).eq.0) then
681 2 itr=itr+1
682 2 write(*,*) 'itr=',itr
683 2 itr_indice(itr)=iq
684 endif !if (iso_num(iq).eq.0) then
685 enddo
686
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if (itr.ne.nqtottr) then
687 CALL abort_gcm('infotrac_init','pb dans le calcul de nqtottr',1)
688 endif
689 1 write(lunout,*) 'itr_indice=',itr_indice
690 ! endif !if (ntraciso.gt.0) then
691
692 !-----------------------------------------------------------------------
693 ! Finalize :
694 !
695
4/8
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
1 DEALLOCATE(tnom_0, hadv, vadv,tnom_transp)
696
697 1 WRITE(lunout,*) 'infotrac init fin'
698
699
5/10
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
1 END SUBROUTINE infotrac_init
700
701 1 SUBROUTINE infotrac_isoinit(tnom_0,nqtrue)
702
703 68 use IOIPSL
704 implicit none
705
706 ! inputs
707 INTEGER nqtrue
708 CHARACTER(len=30) tnom_0(nqtrue)
709
710 ! locals
711 CHARACTER(len=3), DIMENSION(niso_possibles) :: tnom_iso
712 INTEGER, ALLOCATABLE,DIMENSION(:,:) :: nb_iso,nb_traciso
713 INTEGER, ALLOCATABLE,DIMENSION(:) :: nb_isoind
714 INTEGER :: ntraceurs_zone_prec,iq,phase,ixt,iiso,izone
715 CHARACTER(len=19) :: tnom_trac
716 INCLUDE "iniprint.h"
717
718
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 tnom_iso=(/'eau','HDO','O18','O17','HTO'/)
719
720
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
1 ALLOCATE(nb_iso(niso_possibles,nqo))
721
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
1 ALLOCATE(nb_isoind(nqo))
722
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 ALLOCATE(nb_traciso(niso_possibles,nqo))
723
3/6
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
1 ALLOCATE(iso_num(nqtot))
724
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(iso_indnum(nqtot))
725
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(zone_num(nqtot))
726
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(phase_num(nqtot))
727
728
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 iso_num(:)=0
729
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 iso_indnum(:)=0
730
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 zone_num(:)=0
731
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 phase_num(:)=0
732 1 indnum_fn_num(:)=0
733 1 use_iso(:)=.false.
734
4/4
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 15 times.
✓ Branch 3 taken 3 times.
19 nb_iso(:,:)=0
735
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 nb_isoind(:)=0
736
4/4
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 15 times.
✓ Branch 3 taken 3 times.
19 nb_traciso(:,:)=0
737 1 niso=0
738 1 ntraceurs_zone=0
739 1 ntraceurs_zone_prec=0
740 1 ntraciso=0
741
742
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 do iq=nqo+1,nqtot
743 ! write(lunout,*) 'infotrac 569: iq,tnom_0(iq)=',iq,tnom_0(iq)
744
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
8 do phase=1,nqo
745
2/2
✓ Branch 0 taken 30 times.
✓ Branch 1 taken 6 times.
38 do ixt= 1,niso_possibles
746
2/4
✓ Branch 2 taken 30 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 30 times.
✗ Branch 5 not taken.
30 tnom_trac=trim(tnom_0(phase))//'_'
747
1/2
✓ Branch 1 taken 30 times.
✗ Branch 2 not taken.
30 tnom_trac=trim(tnom_trac)//trim(tnom_iso(ixt))
748 ! write(*,*) 'phase,ixt,tnom_trac=',phase,ixt,tnom_trac
749
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 30 times.
36 IF (tnom_0(iq) == tnom_trac) then
750 ! write(lunout,*) 'Ce traceur est un isotope'
751 nb_iso(ixt,phase)=nb_iso(ixt,phase)+1
752 nb_isoind(phase)=nb_isoind(phase)+1
753 iso_num(iq)=ixt
754 iso_indnum(iq)=nb_isoind(phase)
755 indnum_fn_num(ixt)=iso_indnum(iq)
756 phase_num(iq)=phase
757 ! write(lunout,*) 'iso_num(iq)=',iso_num(iq)
758 ! write(lunout,*) 'iso_indnum(iq)=',iso_indnum(iq)
759 ! write(lunout,*) 'indnum_fn_num(ixt)=',indnum_fn_num(ixt)
760 ! write(lunout,*) 'phase_num(iq)=',phase_num(iq)
761 goto 20
762
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 30 times.
30 else if (iqpere(iq).gt.0) then
763 if (tnom_0(iqpere(iq)) == tnom_trac) then
764 ! write(lunout,*) 'Ce traceur est le fils d''un isotope'
765 ! c'est un traceur d'isotope
766 nb_traciso(ixt,phase)=nb_traciso(ixt,phase)+1
767 iso_num(iq)=ixt
768 iso_indnum(iq)=indnum_fn_num(ixt)
769 zone_num(iq)=nb_traciso(ixt,phase)
770 phase_num(iq)=phase
771 ! write(lunout,*) 'iso_num(iq)=',iso_num(iq)
772 ! write(lunout,*) 'phase_num(iq)=',phase_num(iq)
773 ! write(lunout,*) 'zone_num(iq)=',zone_num(iq)
774 goto 20
775 endif !if (tnom_0(iqpere(iq)) == trim(tnom_0(phase))//trim(tnom_iso(ixt))) then
776 endif !IF (tnom_0(iq) == trim(tnom_0(phase))//trim(tnom_iso(ixt))) then
777 enddo !do ixt= niso_possibles
778 enddo !do phase=1,nqo
779 1 20 continue
780 enddo !do iq=1,nqtot
781
782 ! write(lunout,*) 'iso_num=',iso_num
783 ! write(lunout,*) 'iso_indnum=',iso_indnum
784 ! write(lunout,*) 'zone_num=',zone_num
785 ! write(lunout,*) 'phase_num=',phase_num
786 ! write(lunout,*) 'indnum_fn_num=',indnum_fn_num
787
788
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 do ixt= 1,niso_possibles
789
790
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
6 if (nb_iso(ixt,1).eq.1) then
791 ! on verifie que toutes les phases ont le meme nombre de
792 ! traceurs
793 do phase=2,nqo
794 if (nb_iso(ixt,phase).ne.nb_iso(ixt,1)) then
795 ! write(lunout,*) 'ixt,phase,nb_iso=',ixt,phase,nb_iso(ixt,phase)
796 CALL abort_gcm('infotrac_init','Phases must have same number of isotopes',1)
797 endif
798 enddo !do phase=2,nqo
799
800 niso=niso+1
801 use_iso(ixt)=.true.
802 ntraceurs_zone=nb_traciso(ixt,1)
803
804 ! on verifie que toutes les phases ont le meme nombre de
805 ! traceurs
806 do phase=2,nqo
807 if (nb_traciso(ixt,phase).ne.ntraceurs_zone) then
808 write(lunout,*) 'ixt,phase,nb_traciso=',ixt,phase,nb_traciso(ixt,phase)
809 write(lunout,*) 'ntraceurs_zone=',ntraceurs_zone
810 CALL abort_gcm('infotrac_init','Phases must have same number of tracers',1)
811 endif
812 enddo !do phase=2,nqo
813 ! on verifie que tous les isotopes ont le meme nombre de
814 ! traceurs
815 if (ntraceurs_zone_prec.gt.0) then
816 if (ntraceurs_zone.eq.ntraceurs_zone_prec) then
817 ntraceurs_zone_prec=ntraceurs_zone
818 else !if (ntraceurs_zone.eq.ntraceurs_zone_prec) then
819 write(*,*) 'ntraceurs_zone_prec,ntraceurs_zone=',ntraceurs_zone_prec,ntraceurs_zone
820 CALL abort_gcm('infotrac_init', &
821 &'Isotope tracers are not well defined in traceur.def',1)
822 endif !if (ntraceurs_zone.eq.ntraceurs_zone_prec) then
823 endif !if (ntraceurs_zone_prec.gt.0) then
824
825
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
5 else if (nb_iso(ixt,1).ne.0) then
826 WRITE(lunout,*) 'nqo,ixt=',nqo,ixt
827 WRITE(lunout,*) 'nb_iso(ixt,1)=',nb_iso(ixt,1)
828 CALL abort_gcm('infotrac_init','Isotopes are not well defined in traceur.def',1)
829 endif !if (nb_iso(ixt,1).eq.1) then
830 enddo ! do ixt= niso_possibles
831
832 ! dimensions isotopique:
833 1 ntraciso=niso*(ntraceurs_zone+1)
834 ! WRITE(lunout,*) 'niso=',niso
835 ! WRITE(lunout,*) 'ntraceurs_zone,ntraciso=',ntraceurs_zone,ntraciso
836
837 ! flags isotopiques:
838
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if (niso.gt.0) then
839 ok_isotopes=.true.
840 else
841 1 ok_isotopes=.false.
842 endif
843 ! WRITE(lunout,*) 'ok_isotopes=',ok_isotopes
844
845
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if (ok_isotopes) then
846 ok_iso_verif=.false.
847 call getin('ok_iso_verif',ok_iso_verif)
848 ok_init_iso=.false.
849 call getin('ok_init_iso',ok_init_iso)
850 tnat=(/1.0,155.76e-6,2005.2e-6,0.004/100.,0.0/)
851 alpha_ideal=(/1.0,1.01,1.006,1.003,1.0/)
852 endif !if (ok_isotopes) then
853 ! WRITE(lunout,*) 'ok_iso_verif=',ok_iso_verif
854 ! WRITE(lunout,*) 'ok_init_iso=',ok_init_iso
855
856
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if (ntraceurs_zone.gt.0) then
857 ok_isotrac=.true.
858 else
859 1 ok_isotrac=.false.
860 endif
861 ! WRITE(lunout,*) 'ok_isotrac=',ok_isotrac
862
863 ! remplissage du tableau iqiso(ntraciso,phase)
864
3/6
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
1 ALLOCATE(iqiso(ntraciso,nqo))
865
3/4
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
4 iqiso(:,:)=0
866
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 do iq=1,nqtot
867
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
6 if (iso_num(iq).gt.0) then
868 ixt=iso_indnum(iq)+zone_num(iq)*niso
869 iqiso(ixt,phase_num(iq))=iq
870 endif
871 enddo
872 ! WRITE(lunout,*) 'iqiso=',iqiso
873
874 ! replissage du tableau index_trac(ntraceurs_zone,niso)
875
3/6
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
1 ALLOCATE(index_trac(ntraceurs_zone,niso))
876
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if (ok_isotrac) then
877 do iiso=1,niso
878 do izone=1,ntraceurs_zone
879 index_trac(izone,iiso)=iiso+izone*niso
880 enddo
881 enddo
882 else !if (ok_isotrac) then
883
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
1 index_trac(:,:)=0.0
884 endif !if (ok_isotrac) then
885 ! write(lunout,*) 'index_trac=',index_trac
886
887 ! Finalize :
888
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 DEALLOCATE(nb_iso)
889
890
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
1 END SUBROUTINE infotrac_isoinit
891
892 END MODULE infotrac
893