GCC Code Coverage Report


Directory: ./
File: phys/infotrac_phy.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 36 65 55.4%
Branches: 32 142 22.5%

Line Branch Exec Source
1
2 ! $Id: $
3
4 MODULE infotrac_phy
5
6 ! Infotrac for physics; for now contains the same information as infotrac for
7 ! the dynamics (could be further cleaned) and is initialized using values
8 ! provided by the dynamics
9
10 ! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
11 INTEGER, SAVE :: nqtot
12 !$OMP THREADPRIVATE(nqtot)
13
14 !CR: on ajoute le nombre de traceurs de l eau
15 INTEGER, SAVE :: nqo
16 !$OMP THREADPRIVATE(nqo)
17
18 ! nbtr : number of tracers not including higher order of moment or water vapor or liquid
19 ! number of tracers used in the physics
20 INTEGER, SAVE :: nbtr
21 !$OMP THREADPRIVATE(nbtr)
22
23 INTEGER, SAVE :: nqtottr
24 !$OMP THREADPRIVATE(nqtottr)
25
26 ! ThL : number of CO2 tracers ModThL
27 INTEGER, SAVE :: nqCO2
28 !$OMP THREADPRIVATE(nqCO2)
29
30
31 ! CRisi: nb traceurs pères= directement advectés par l'air
32 INTEGER, SAVE :: nqperes
33 !$OMP THREADPRIVATE(nqperes)
34
35 ! Name variables
36 CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
37 CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
38 !$OMP THREADPRIVATE(tname,ttext)
39
40 !! iadv : index of trasport schema for each tracer
41 ! INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iadv
42
43 ! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
44 ! dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
45 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: niadv ! equivalent dyn / physique
46 !$OMP THREADPRIVATE(niadv)
47
48 ! CRisi: tableaux de fils
49 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: nqfils
50 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: nqdesc ! nombres de fils + nombre de tous les petits fils sur toutes les générations
51 INTEGER, SAVE :: nqdesc_tot
52 INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: iqfils
53 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iqpere
54 !$OMP THREADPRIVATE(nqfils,nqdesc,nqdesc_tot,iqfils,iqpere)
55
56 ! conv_flg(it)=0 : convection desactivated for tracer number it
57 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: conv_flg
58 !$OMP THREADPRIVATE(conv_flg)
59
60 ! pbl_flg(it)=0 : boundary layer diffusion desactivaded for tracer number it
61 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: pbl_flg
62 !$OMP THREADPRIVATE(pbl_flg)
63
64 CHARACTER(len=4),SAVE :: type_trac
65 !$OMP THREADPRIVATE(type_trac)
66 CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
67 !$OMP THREADPRIVATE(solsym)
68
69 ! CRisi: cas particulier des isotopes
70 LOGICAL,SAVE :: ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso
71 !$OMP THREADPRIVATE(ok_isotopes,ok_iso_verif,ok_isotrac,ok_init_iso)
72 INTEGER :: niso_possibles
73 PARAMETER ( niso_possibles=5)
74 real, DIMENSION (niso_possibles),SAVE :: tnat,alpha_ideal
75 !$OMP THREADPRIVATE(tnat,alpha_ideal)
76 LOGICAL, DIMENSION(niso_possibles),SAVE :: use_iso
77 !$OMP THREADPRIVATE(use_iso)
78 INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: iqiso ! donne indice iq en fn de (ixt,phase)
79 !$OMP THREADPRIVATE(iqiso)
80 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iso_num ! donne numéro iso entre 1 et niso_possibles en fn de nqtot
81 !$OMP THREADPRIVATE(iso_num)
82 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: iso_indnum ! donne numéro iso entre 1 et niso effectif en fn de nqtot
83 !$OMP THREADPRIVATE(iso_indnum)
84 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: zone_num ! donne numéro de la zone de tracage en fn de nqtot
85 !$OMP THREADPRIVATE(zone_num)
86 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: phase_num ! donne numéro de la zone de tracage en fn de nqtot
87 !$OMP THREADPRIVATE(phase_num)
88 INTEGER, DIMENSION(niso_possibles), SAVE :: indnum_fn_num ! donne indice entre entre 1 et niso en fonction du numéro d isotope entre 1 et niso_possibles
89 !$OMP THREADPRIVATE(indnum_fn_num)
90 INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: index_trac ! numéro ixt en fn izone, indnum entre 1 et niso
91 !$OMP THREADPRIVATE(index_trac)
92 INTEGER,SAVE :: niso,ntraceurs_zone,ntraciso
93 !$OMP THREADPRIVATE(niso,ntraceurs_zone,ntraciso)
94
95 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: itr_indice ! numéro iq entre 1 et nqtot qui correspond au traceur itr entre 1 et nqtottr
96 !$OMP THREADPRIVATE(itr_indice)
97
98 CONTAINS
99
100 1 SUBROUTINE init_infotrac_phy(nqtot_,nqo_,nbtr_,nqtottr_,nqCO2_,tname_,ttext_,type_trac_,&
101 1 niadv_,conv_flg_,pbl_flg_,solsym_,&
102 1 nqfils_,nqdesc_,nqdesc_tot_,iqfils_,iqpere_,&
103 ok_isotopes_,ok_iso_verif_,ok_isotrac_,&
104 1 ok_init_iso_,niso_possibles_,tnat_,&
105 1 alpha_ideal_,use_iso_,iqiso_,iso_num_,&
106 iso_indnum_,zone_num_,phase_num_,&
107 1 indnum_fn_num_,index_trac_,&
108 1 niso_,ntraceurs_zone_,ntraciso_,itr_indice_&
109 )
110
111 ! transfer information on tracers from dynamics to physics
112 USE print_control_mod, ONLY: prt_level, lunout
113 IMPLICIT NONE
114
115 INTEGER,INTENT(IN) :: nqtot_
116 INTEGER,INTENT(IN) :: nqo_
117 INTEGER,INTENT(IN) :: nbtr_
118 INTEGER,INTENT(IN) :: nqtottr_
119 INTEGER,INTENT(IN) :: nqCO2_
120 CHARACTER(len=20),INTENT(IN) :: tname_(nqtot_) ! tracer short name for restart and diagnostics
121 CHARACTER(len=23),INTENT(IN) :: ttext_(nqtot_) ! tracer long name for diagnostics
122 CHARACTER(len=4),INTENT(IN) :: type_trac_
123 INTEGER,INTENT(IN) :: niadv_ (nqtot_) ! equivalent dyn / physique
124 INTEGER,INTENT(IN) :: conv_flg_(nbtr_)
125 INTEGER,INTENT(IN) :: pbl_flg_(nbtr_)
126 CHARACTER(len=8),INTENT(IN) :: solsym_(nbtr_)
127 ! Isotopes:
128 INTEGER,INTENT(IN) :: nqfils_(nqtot_)
129 INTEGER,INTENT(IN) :: nqdesc_(nqtot_)
130 INTEGER,INTENT(IN) :: nqdesc_tot_
131 INTEGER,INTENT(IN) :: iqfils_(nqtot_,nqtot_)
132 INTEGER,INTENT(IN) :: iqpere_(nqtot_)
133 LOGICAL,INTENT(IN) :: ok_isotopes_
134 LOGICAL,INTENT(IN) :: ok_iso_verif_
135 LOGICAL,INTENT(IN) :: ok_isotrac_
136 LOGICAL,INTENT(IN) :: ok_init_iso_
137 INTEGER,INTENT(IN) :: niso_possibles_
138 REAL,INTENT(IN) :: tnat_(niso_possibles_)
139 REAL,INTENT(IN) :: alpha_ideal_(niso_possibles_)
140 LOGICAL,INTENT(IN) :: use_iso_(niso_possibles_)
141 INTEGER,INTENT(IN) :: iqiso_(ntraciso_,nqo_)
142 INTEGER,INTENT(IN) :: iso_num_(nqtot_)
143 INTEGER,INTENT(IN) :: iso_indnum_(nqtot_)
144 INTEGER,INTENT(IN) :: zone_num_(nqtot_)
145 INTEGER,INTENT(IN) :: phase_num_(nqtot_)
146 INTEGER,INTENT(IN) :: indnum_fn_num_(niso_possibles_)
147 INTEGER,INTENT(IN) :: index_trac_(ntraceurs_zone_,niso_)
148 INTEGER,INTENT(IN) :: niso_
149 INTEGER,INTENT(IN) :: ntraceurs_zone_
150 INTEGER,INTENT(IN) :: ntraciso_
151 INTEGER,INTENT(IN) :: itr_indice_(nqtottr_)
152
153 CHARACTER(LEN=30) :: modname="init_infotrac_phy"
154
155 1 nqtot=nqtot_
156 1 nqo=nqo_
157 1 nbtr=nbtr_
158 1 nqCO2=nqCO2_
159 1 nqtottr=nqtottr_
160
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(tname(nqtot))
161
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 tname(:) = tname_(:)
162
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(ttext(nqtot))
163
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 ttext(:) = ttext_(:)
164 1 type_trac = type_trac_
165
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(niadv(nqtot))
166
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 niadv(:)=niadv_(:)
167
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(conv_flg(nbtr))
168
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 conv_flg(:)=conv_flg_(:)
169
2/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ALLOCATE(pbl_flg(nbtr))
170
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 pbl_flg(:)=pbl_flg_(:)
171
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(solsym(nbtr))
172
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 solsym(:)=solsym_(:)
173
174
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF(prt_level.ge.1) THEN
175 write(lunout,*) TRIM(modname)//": nqtot,nqo,nbtr,nqCO2",nqtot,nqo,nbtr,nqCO2
176 ENDIF
177
178 ! Isotopes:
179
180 ! First check that the "niso_possibles" has the correct value
181
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (niso_possibles.ne.niso_possibles_) THEN
182 CALL abort_physic(modname,&
183 "wrong value for parameter niso_possibles in infotrac_phy",1)
184 ENDIF
185
186 1 ok_isotopes=ok_isotopes_
187 1 ok_iso_verif=ok_iso_verif_
188 1 ok_isotrac=ok_isotrac_
189 1 ok_init_iso=ok_init_iso_
190
191 1 niso=niso_
192 1 ntraceurs_zone=ntraceurs_zone_
193 1 ntraciso=ntraciso_
194
195
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ok_isotopes) THEN
196 ALLOCATE(nqfils(nqtot))
197 nqfils(:)=nqfils_(:)
198 ALLOCATE(nqdesc(nqtot))
199 nqdesc(:)=nqdesc_(:)
200 nqdesc_tot=nqdesc_tot_
201 ALLOCATE(iqfils(nqtot,nqtot))
202 iqfils(:,:)=iqfils_(:,:)
203 ALLOCATE(iqpere(nqtot))
204 iqpere(:)=iqpere_(:)
205
206 tnat(:)=tnat_(:)
207 alpha_ideal(:)=alpha_ideal_(:)
208 use_iso(:)=use_iso_(:)
209
210 ALLOCATE(iqiso(ntraciso,nqo))
211 iqiso(:,:)=iqiso_(:,:)
212 ALLOCATE(iso_num(nqtot))
213 iso_num(:)=iso_num_(:)
214 ALLOCATE(iso_indnum(nqtot))
215 iso_indnum(:)=iso_indnum_(:)
216 ALLOCATE(zone_num(nqtot))
217 zone_num(:)=zone_num_(:)
218 ALLOCATE(phase_num(nqtot))
219 phase_num(:)=phase_num_(:)
220
221 indnum_fn_num(:)=indnum_fn_num_(:)
222
223 ALLOCATE(index_trac(ntraceurs_zone,niso))
224 index_trac(:,:)=index_trac_(:,:)
225
226 ALLOCATE(itr_indice(nqtottr))
227 itr_indice(:)=itr_indice_(:)
228 ENDIF ! of IF(ok_isotopes)
229
230 1 END SUBROUTINE init_infotrac_phy
231
232 END MODULE infotrac_phy
233