GCC Code Coverage Report


Directory: ./
File: phys/thermcell_height.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 45 51 88.2%
Branches: 43 46 93.5%

Line Branch Exec Source
1 480 SUBROUTINE thermcell_height(ngrid,nlay,lalim,lmin,linter,lmix, &
2 480 & zw2,zlev,lmax,zmax,zmax0,zmix,wmax,lev_out)
3
4 !-----------------------------------------------------------------------------
5 !thermcell_height: calcul des caracteristiques du thermique: zmax,wmax,zmix
6 !-----------------------------------------------------------------------------
7 IMPLICIT NONE
8 integer :: iflag_thermals,nsplit_thermals
9
10 !!! nrlmd le 10/04/2012
11 integer :: iflag_trig_bl,iflag_clos_bl
12 integer :: tau_trig_shallow,tau_trig_deep
13 real :: s_trig
14 !!! fin nrlmd le 10/04/2012
15
16 real,parameter :: r_aspect_thermals=2.,l_mix_thermals=30.
17 real :: alp_bl_k
18 real :: tau_thermals,fact_thermals_ed_dz
19 integer,parameter :: w2di_thermals=0
20 integer :: isplit
21
22 integer :: iflag_coupl,iflag_clos,iflag_wake
23 integer :: iflag_thermals_ed,iflag_thermals_optflux,iflag_thermals_closure
24
25 common/ctherm1/iflag_thermals,nsplit_thermals,iflag_thermals_closure
26 common/ctherm2/tau_thermals,alp_bl_k,fact_thermals_ed_dz
27 common/ctherm4/iflag_coupl,iflag_clos,iflag_wake
28 common/ctherm5/iflag_thermals_ed,iflag_thermals_optflux
29
30 !!! nrlmd le 10/04/2012
31 common/ctherm6/iflag_trig_bl,iflag_clos_bl
32 common/ctherm7/tau_trig_shallow,tau_trig_deep
33 common/ctherm8/s_trig
34 !!! fin nrlmd le 10/04/2012
35
36 !$OMP THREADPRIVATE(/ctherm1/,/ctherm2/,/ctherm4/,/ctherm5/)
37 !$OMP THREADPRIVATE(/ctherm6/,/ctherm7/,/ctherm8/)
38
39 INTEGER ig,l
40 INTEGER ngrid,nlay
41 INTEGER lalim(ngrid),lmin(ngrid)
42 INTEGER lmix(ngrid)
43 REAL linter(ngrid)
44 integer lev_out ! niveau pour les print
45
46 REAL zw2(ngrid,nlay+1)
47 REAL zlev(ngrid,nlay+1)
48
49 REAL wmax(ngrid)
50 INTEGER lmax(ngrid)
51 REAL zmax(ngrid)
52 REAL zmax0(ngrid)
53 REAL zmix(ngrid)
54 REAL num(ngrid)
55 480 REAL denom(ngrid)
56
57 480 REAL zlevinter(ngrid)
58
59 !calcul de la hauteur max du thermique
60
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 do ig=1,ngrid
61 477600 lmax(ig)=lalim(ig)
62 enddo
63
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 do ig=1,ngrid
64
2/2
✓ Branch 0 taken 17520899 times.
✓ Branch 1 taken 477120 times.
17998499 do l=nlay,lalim(ig)+1,-1
65
2/2
✓ Branch 0 taken 16824070 times.
✓ Branch 1 taken 696829 times.
17998019 if (zw2(ig,l).le.1.e-10) then
66 16824070 lmax(ig)=l-1
67 endif
68 enddo
69 enddo
70
71 ! On traite le cas particulier qu'il faudrait �viter ou le thermique
72 ! atteind le haut du modele ...
73
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 do ig=1,ngrid
74
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 477120 times.
477600 if ( zw2(ig,nlay) > 1.e-10 ) then
75 print*,'WARNING !!!!! W2 thermiques non nul derniere couche '
76 lmax(ig)=nlay
77 endif
78 enddo
79
80 ! pas de thermique si couche 1 stable
81
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 do ig=1,ngrid
82
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 477120 times.
477600 if (lmin(ig).gt.1) then
83 lmax(ig)=1
84 lmin(ig)=1
85 lalim(ig)=1
86 endif
87 enddo
88 !
89 ! Determination de zw2 max
90
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 do ig=1,ngrid
91 477600 wmax(ig)=0.
92 enddo
93
94
2/2
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
19200 do l=1,nlay
95
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626880 do ig=1,ngrid
96
2/2
✓ Branch 0 taken 1783610 times.
✓ Branch 1 taken 16824070 times.
18626400 if (l.le.lmax(ig)) then
97
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1783610 times.
1783610 if (zw2(ig,l).lt.0.)then
98 print*,'pb2 zw2<0'
99 endif
100 1783610 zw2(ig,l)=sqrt(zw2(ig,l))
101 1783610 wmax(ig)=max(wmax(ig),zw2(ig,l))
102 else
103 16824070 zw2(ig,l)=0.
104 endif
105 enddo
106 enddo
107
108 ! Longueur caracteristique correspondant a la hauteur des thermiques.
109
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 do ig=1,ngrid
110 477120 zmax(ig)=0.
111 477600 zlevinter(ig)=zlev(ig,1)
112 enddo
113
114 ! if (iflag_thermals_ed.ge.1) then
115 if (1==0) then
116 !CR:date de quand le calcul du zmax continu etait buggue
117 num(:)=0.
118 denom(:)=0.
119 do ig=1,ngrid
120 do l=1,nlay
121 num(ig)=num(ig)+zw2(ig,l)*zlev(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
122 denom(ig)=denom(ig)+zw2(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
123 enddo
124 enddo
125 do ig=1,ngrid
126 if (denom(ig).gt.1.e-10) then
127 zmax(ig)=2.*num(ig)/denom(ig)
128 zmax0(ig)=zmax(ig)
129 endif
130 enddo
131
132 else
133 !CR:Calcul de zmax continu via le linter
134
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 do ig=1,ngrid
135 ! calcul de zlevinter
136 zlevinter(ig)=(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))* &
137 & linter(ig)+zlev(ig,lmax(ig))-lmax(ig)*(zlev(ig,lmax(ig)+1) &
138 477120 & -zlev(ig,lmax(ig)))
139 !pour le cas ou on prend tjs lmin=1
140 ! zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,lmin(ig)))
141 477120 zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,1))
142 477600 zmax0(ig)=zmax(ig)
143 enddo
144
145
146 endif
147 !endif iflag_thermals_ed
148 !
149 ! def de zmix continu (profil parabolique des vitesses)
150
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 do ig=1,ngrid
151
2/2
✓ Branch 0 taken 240493 times.
✓ Branch 1 taken 236627 times.
477120 if (lmix(ig).gt.1) then
152 ! test
153
2/2
✓ Branch 0 taken 240491 times.
✓ Branch 1 taken 2 times.
240493 if (((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig))) &
154 & *((zlev(ig,lmix(ig)))-(zlev(ig,lmix(ig)+1))) &
155 & -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1)) &
156 & *((zlev(ig,lmix(ig)-1))-(zlev(ig,lmix(ig))))).gt.1e-10) &
157 & then
158 !
159 zmix(ig)=((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig))) &
160 & *((zlev(ig,lmix(ig)))**2-(zlev(ig,lmix(ig)+1))**2) &
161 & -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1)) &
162 & *((zlev(ig,lmix(ig)-1))**2-(zlev(ig,lmix(ig)))**2)) &
163 & /(2.*((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig))) &
164 & *((zlev(ig,lmix(ig)))-(zlev(ig,lmix(ig)+1))) &
165 & -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1)) &
166 240491 & *((zlev(ig,lmix(ig)-1))-(zlev(ig,lmix(ig))))))
167 else
168 2 zmix(ig)=zlev(ig,lmix(ig))
169 2 print*,'pb zmix'
170 endif
171 else
172 236627 zmix(ig)=0.
173 endif
174 !test
175
2/2
✓ Branch 0 taken 230559 times.
✓ Branch 1 taken 246561 times.
477600 if ((zmax(ig)-zmix(ig)).le.0.) then
176 230559 zmix(ig)=0.9*zmax(ig)
177 ! print*,'pb zmix>zmax'
178 endif
179 enddo
180 !
181 ! calcul du nouveau lmix correspondant
182
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 do ig=1,ngrid
183
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 477120 times.
19085280 do l=1,nlay
184
4/4
✓ Branch 0 taken 1534016 times.
✓ Branch 1 taken 17073664 times.
✓ Branch 2 taken 477120 times.
✓ Branch 3 taken 1056896 times.
18607680 if (zmix(ig).ge.zlev(ig,l).and. &
185 477120 & zmix(ig).lt.zlev(ig,l+1)) then
186 477120 lmix(ig)=l
187 endif
188 enddo
189 enddo
190 !
191 480 return
192 end
193