GCC Code Coverage Report


Directory: ./
File: phys/wx_pbl_var_mod.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 211 334 63.2%
Branches: 414 862 48.0%

Line Branch Exec Source
1 MODULE wx_pbl_var_mod
2 !
3 ! Split Planetary Boundary Layer variables
4 !
5 ! This module manages the variables necessary for the splitting of the boundary layer
6 !
7 !
8 USE dimphy
9
10 IMPLICIT NONE
11
12 REAL, PROTECTED, SAVE :: eps_1, fqsat, smallestreal
13 !$OMP THREADPRIVATE(eps_1, fqsat, smallestreal)
14 !
15 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: C_p, L_v
16 !$OMP THREADPRIVATE(C_p, L_v)
17 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: Ts0, dTs0
18 !$OMP THREADPRIVATE(Ts0, dTs0)
19 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: Ts0_x, Ts0_w
20 !$OMP THREADPRIVATE(Ts0_x, Ts0_w)
21 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: qsat0, dqsatdT0
22 !$OMP THREADPRIVATE(qsat0, dqsatdT0)
23 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: qsat0_x, dqsatdT0_x
24 !$OMP THREADPRIVATE(qsat0_x, dqsatdT0_x)
25 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: qsat0_w, dqsatdT0_w
26 !$OMP THREADPRIVATE(qsat0_w, dqsatdT0_w)
27 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: QQ_b, dd_QQ
28 !$OMP THREADPRIVATE(QQ_b, dd_QQ)
29 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: QQ_x, QQ_w
30 !$OMP THREADPRIVATE(QQ_x, QQ_w)
31 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: qsatsrf0_x, qsatsrf0_w
32 !$OMP THREADPRIVATE(qsatsrf0_x, qsatsrf0_w)
33 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dqsatsrf0
34 !$OMP THREADPRIVATE(dqsatsrf0)
35 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: q1_0b
36 !$OMP THREADPRIVATE(q1_0b)
37 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dd_Cdragh, dd_Cdragm, dd_Cdragq
38 !$OMP THREADPRIVATE(dd_Cdragh, dd_Cdragm, dd_Cdragq )
39 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: Kech_h, Kech_h_x, Kech_h_w ! Energy exchange coefficients
40 !$OMP THREADPRIVATE(Kech_h, Kech_h_x, Kech_h_w)
41 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: Kech_q, Kech_q_x, Kech_q_w ! Moisture exchange coefficients
42 !$OMP THREADPRIVATE(Kech_q, Kech_q_x, Kech_q_w)
43 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: Kech_m, Kech_m_x, Kech_m_w ! Momentum exchange coefficients
44 !$OMP THREADPRIVATE(Kech_m, Kech_m_x, Kech_m_w)
45 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: Kech_Tp, Kech_T_px, Kech_T_pw
46 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dd_KTp, KxKwTp
47 !$OMP THREADPRIVATE(Kech_Tp, Kech_T_px, Kech_T_pw, dd_KTp, KxKwTp)
48 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dd_AT, dd_BT
49 !$OMP THREADPRIVATE(dd_AT, dd_BT)
50 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: Kech_Qp, Kech_Q_px, Kech_Q_pw
51 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dd_KQp, KxKwQp
52 !$OMP THREADPRIVATE(Kech_Qp, Kech_Q_px, Kech_Q_pw, dd_KQp, KxKwQp)
53 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: Kech_Qs, Kech_Q_sx, Kech_Q_sw
54 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dd_KQs, KxKwQs
55 !$OMP THREADPRIVATE(Kech_Qs, Kech_Q_sx, Kech_Q_sw, dd_KQs, KxKwQs)
56 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dd_AQ, dd_BQ
57 !$OMP THREADPRIVATE(dd_AQ, dd_BQ)
58 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: AQ_x, AQ_w, BQ_x, BQ_w
59 !$OMP THREADPRIVATE(AQ_x, AQ_w, BQ_x, BQ_w)
60 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: Kech_Up, Kech_U_px, Kech_U_pw
61 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dd_KUp, KxKwUp
62 !$OMP THREADPRIVATE(Kech_Up, Kech_U_px, Kech_U_pw, dd_KUp, KxKwUp)
63 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dd_AU, dd_BU
64 !$OMP THREADPRIVATE(dd_AU, dd_BU)
65 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: Kech_Vp, Kech_V_px, Kech_V_pw
66 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dd_KVp, KxKwVp
67 !$OMP THREADPRIVATE(Kech_Vp, Kech_V_px, Kech_V_pw, dd_KVp, KxKwVp)
68 REAL, ALLOCATABLE, PROTECTED, DIMENSION(:), SAVE :: dd_AV, dd_BV
69 !$OMP THREADPRIVATE(dd_AV, dd_BV)
70
71 CONTAINS
72 !
73 !****************************************************************************************
74 !
75 1 SUBROUTINE wx_pbl_init
76
77 ! Local variables
78 !****************************************************************************************
79 INTEGER :: ierr
80
81
82 !****************************************************************************************
83 ! Allocate module variables
84 !
85 !****************************************************************************************
86
87 ierr = 0
88
89
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(C_p(klon), stat=ierr)
90
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
91
92
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(L_v(klon), stat=ierr)
93
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
94
95
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Ts0(klon), stat=ierr)
96
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
97
98
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dTs0(klon), stat=ierr)
99
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
100
101
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Ts0_x(klon), stat=ierr)
102
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
103
104
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Ts0_w(klon), stat=ierr)
105
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
106
107
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(qsat0(klon), stat=ierr)
108
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
109
110
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dqsatdT0(klon), stat=ierr)
111
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
112
113
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(qsat0_x(klon), stat=ierr)
114
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
115
116
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dqsatdT0_x(klon), stat=ierr)
117
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
118
119
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(qsat0_w(klon), stat=ierr)
120
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
121
122
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dqsatdT0_w(klon), stat=ierr)
123
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
124
125
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(q1_0b(klon), stat=ierr)
126
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
127
128
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(QQ_b(klon), stat=ierr)
129
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
130
131
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_QQ(klon), stat=ierr)
132
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
133
134
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(QQ_x(klon), stat=ierr)
135
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
136
137
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(QQ_w(klon), stat=ierr)
138
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
139
140
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(qsatsrf0_x(klon), stat=ierr)
141
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
142
143
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(qsatsrf0_w(klon), stat=ierr)
144
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
145
146
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dqsatsrf0(klon), stat=ierr)
147
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
148
149
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_Cdragh(klon), stat=ierr)
150
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
151
152
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_Cdragm(klon), stat=ierr)
153
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
154
155
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_Cdragq(klon), stat=ierr)
156
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
157
158
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_h(klon), stat=ierr)
159
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
160
161
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_h_x(klon), stat=ierr)
162
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
163
164
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_h_w(klon), stat=ierr)
165
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
166
167
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_q(klon), stat=ierr)
168
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
169
170
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_q_x(klon), stat=ierr)
171
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
172
173
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_q_w(klon), stat=ierr)
174
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
175
176
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_m(klon), stat=ierr)
177
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
178
179
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_m_x(klon), stat=ierr)
180
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
181
182
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_m_w(klon), stat=ierr)
183
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
184
185
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_Tp(klon), stat=ierr)
186
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
187
188
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_T_px(klon), stat=ierr)
189
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
190
191
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_T_pw(klon), stat=ierr)
192
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
193
194
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_KTp(klon), stat=ierr)
195
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
196
197
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(KxKwTp(klon), stat=ierr)
198
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
199
200
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_AT(klon), stat=ierr)
201
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
202
203
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_BT(klon), stat=ierr)
204
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
205
206 !----------------------------------------------------------------------------
207
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_Qp(klon), stat=ierr)
208
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
209
210
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_Q_px(klon), stat=ierr)
211
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
212
213
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_Q_pw(klon), stat=ierr)
214
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
215
216
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_KQp(klon), stat=ierr)
217
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
218
219
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(KxKwQp(klon), stat=ierr)
220
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
221
222
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_Qs(klon), stat=ierr)
223
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
224
225
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_Q_sx(klon), stat=ierr)
226
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
227
228
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_Q_sw(klon), stat=ierr)
229
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
230
231
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_KQs(klon), stat=ierr)
232
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
233
234
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(KxKwQs(klon), stat=ierr)
235
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
236
237 !!!!!!!!!!
238
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(AQ_x(klon), stat=ierr)
239
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
240
241
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(AQ_w(klon), stat=ierr)
242
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
243
244
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(BQ_x(klon), stat=ierr)
245
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
246
247
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(BQ_w(klon), stat=ierr)
248
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
249
250
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_AQ(klon), stat=ierr)
251
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
252
253
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_BQ(klon), stat=ierr)
254
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
255
256 !----------------------------------------------------------------------------
257
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_Up(klon), stat=ierr)
258
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
259
260
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_U_px(klon), stat=ierr)
261
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
262
263
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_U_pw(klon), stat=ierr)
264
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
265
266
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_KUp(klon), stat=ierr)
267
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
268
269
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(KxKwUp(klon), stat=ierr)
270
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
271
272
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_AU(klon), stat=ierr)
273
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
274
275
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_BU(klon), stat=ierr)
276
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
277
278 !----------------------------------------------------------------------------
279
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_Vp(klon), stat=ierr)
280
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
281
282
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_V_px(klon), stat=ierr)
283
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
284
285
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(Kech_V_pw(klon), stat=ierr)
286
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
287
288
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_KVp(klon), stat=ierr)
289
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
290
291
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(KxKwVp(klon), stat=ierr)
292
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
293
294
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_AV(klon), stat=ierr)
295
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
296
297
4/8
✓ 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.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
1 ALLOCATE(dd_BV(klon), stat=ierr)
298
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ierr /= 0) CALL abort_physic('wx_pbl_init', 'pb in allocation',1)
299
300 !----------------------------------------------------------------------------
301
302 1 END SUBROUTINE wx_pbl_init
303
304 SUBROUTINE wx_pbl_prelim_0(knon, nsrf, dtime, ypplay, ypaprs, sigw, &
305 yt_s, ydeltat_s, ygustiness, &
306 yt_x, yt_w, yq_x, yq_w, &
307 yu_x, yu_w, yv_x, yv_w, &
308 ycdragh_x, ycdragh_w, ycdragq_x, ycdragq_w, &
309 ycdragm_x, ycdragm_w, &
310 AcoefT_x, AcoefT_w, AcoefQ_x, AcoefQ_w, &
311 AcoefU_x, AcoefU_w, AcoefV_x, AcoefV_w, &
312 BcoefT_x, BcoefT_w, BcoefQ_x, BcoefQ_w, &
313 BcoefU_x, BcoefU_w, BcoefV_x, BcoefV_w, &
314 Kech_h_x_out, Kech_h_w_out, Kech_h_out &
315 )
316 !
317 USE print_control_mod, ONLY: prt_level,lunout
318 USE indice_sol_mod, ONLY: is_oce
319 !
320 INCLUDE "YOMCST.h"
321 INCLUDE "FCTTRE.h"
322 INCLUDE "YOETHF.h"
323 INCLUDE "clesphys.h"
324 !
325 INTEGER, INTENT(IN) :: knon ! number of grid cells
326 INTEGER, INTENT(IN) :: nsrf ! surface type
327 REAL, INTENT(IN) :: dtime ! time step size (s)
328 REAL, DIMENSION(knon,klev), INTENT(IN) :: ypplay ! mid-layer pressure (Pa)
329 REAL, DIMENSION(knon,klev), INTENT(IN) :: ypaprs ! pressure at layer interfaces (pa)
330 REAL, DIMENSION(knon), INTENT(IN) :: sigw ! cold pools fractional area
331 REAL, DIMENSION(knon), INTENT(IN) :: yt_s
332 REAL, DIMENSION(knon), INTENT(IN) :: ydeltat_s
333 REAL, DIMENSION(knon), INTENT(IN) :: ygustiness
334 REAL, DIMENSION(knon,klev), INTENT(IN) :: yt_x, yt_w, yq_x, yq_w
335 REAL, DIMENSION(knon,klev), INTENT(IN) :: yu_x, yu_w, yv_x, yv_w
336 REAL, DIMENSION(knon), INTENT(IN) :: ycdragh_x, ycdragh_w, ycdragq_x, ycdragq_w
337 REAL, DIMENSION(knon), INTENT(IN) :: ycdragm_x, ycdragm_w
338 REAL, DIMENSION(knon), INTENT(IN) :: AcoefT_x, AcoefT_w, AcoefQ_x, AcoefQ_w
339 REAL, DIMENSION(knon), INTENT(IN) :: AcoefU_x, AcoefU_w, AcoefV_x, AcoefV_w
340 REAL, DIMENSION(knon), INTENT(IN) :: BcoefT_x, BcoefT_w, BcoefQ_x, BcoefQ_w
341 REAL, DIMENSION(knon), INTENT(IN) :: BcoefU_x, BcoefU_w, BcoefV_x, BcoefV_w
342 !
343 REAL, DIMENSION(knon), INTENT(OUT) :: Kech_h_x_out, Kech_h_w_out, Kech_h_out
344 !
345 ! Local variables
346 INTEGER :: j
347 REAL :: rho1
348 REAL :: mod_wind_x
349 REAL :: mod_wind_w
350 REAL :: dd_Kh
351 REAL :: dd_Kq
352 REAL :: dd_Km
353 !
354 REAL :: zdelta, zcvm5, zcor, qsat
355 !
356 REAL, DIMENSION(knon) :: sigx ! fractional area of (x) region
357 !
358 !!!
359 !!! jyg le 09/04/2013 ; passage aux nouvelles expressions en differences
360
361 !
362 ! First computations
363 ! ------------------
364 eps_1 = 0.5
365 smallestreal=tiny(smallestreal)
366 !
367 sigx(1:knon) = 1.-sigw(1:knon)
368 ! Compute Cp, Lv, qsat, dqsat_dT.
369 L_v(1:knon) = RLvtt
370 Ts0(1:knon) = yt_s(1:knon)
371 dTs0(1:knon) = ydeltat_s(1:knon)
372 q1_0b(1:knon) = sigw(1:knon)*yq_w(1:knon,1)+sigx(1:knon)*yq_x(1:knon,1)
373 !
374 ! fqsat determination
375 ! -------------------
376 IF (nsrf == is_oce) THEN
377 fqsat = f_qsat_oce
378 ELSE
379 fqsat = 1.
380 ENDIF
381 !
382 !
383 ! Reference state
384 ! ---------------
385 DO j = 1, knon
386 zdelta = MAX(0.,SIGN(1.,RTT-Ts0(j)))
387 zcvm5 = R5LES*(1.-zdelta) + R5IES*zdelta
388 qsat = R2ES*FOEEW(Ts0(j),zdelta)/ypaprs(j,1)
389 qsat = MIN(0.5,qsat)
390 zcor = 1./(1.-RETV*qsat)
391 qsat0(j) = fqsat*qsat*zcor
392 dqsatdT0(j) = fqsat*FOEDE(Ts0(j),zdelta,zcvm5,qsat0(j),zcor)
393 C_p(j) = RCpd + qsat0(j)*(RCpv - RCpd)
394 C_p(j) = RCpd
395 !
396 ! print *,' AAAA wx_pbl0, C_p(j), qsat0(j), Ts0(j) : ', C_p(j), qsat0(j), Ts0(j)
397 ENDDO
398 DO j = 1, knon
399 Ts0_x(j) = Ts0(j) - sigw(j)*dTs0(j)
400 zdelta = MAX(0.,SIGN(1.,RTT-Ts0_x(j)))
401 zcvm5 = R5LES*(1.-zdelta) + R5IES*zdelta
402 !! zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
403 qsat = R2ES*FOEEW(Ts0_x(j),zdelta)/ypaprs(j,1)
404 qsat = MIN(0.5,qsat)
405 zcor = 1./(1.-RETV*qsat)
406 qsat0_x(j) = fqsat*qsat*zcor
407 dqsatdT0_x(j) = fqsat*FOEDE(Ts0_x(j),zdelta,zcvm5,qsat0_x(j),zcor)
408 !! dqsatdT0_x(j) = (RLvtt*(1.-zdelta)+RLSTT*zdelta)*qsat0_x(j)/(Rv*Ts0_x(j)*Ts0_x(j))
409 ENDDO
410 DO j = 1, knon
411 Ts0_w(j) = Ts0(j) + sigx(j)*dTs0(j)
412 zdelta = MAX(0.,SIGN(1.,RTT-Ts0_w(j)))
413 zcvm5 = R5LES*(1.-zdelta) + R5IES*zdelta
414 !! zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
415 qsat = R2ES*FOEEW(Ts0_w(j),zdelta)/ypaprs(j,1)
416 qsat = MIN(0.5,qsat)
417 zcor = 1./(1.-RETV*qsat)
418 qsat0_w(j) = fqsat*qsat*zcor
419 dqsatdT0_w(j) = fqsat*FOEDE(Ts0_w(j),zdelta,zcvm5,qsat0_w(j),zcor)
420 !! dqsatdT0_w(j) = (RLvtt*(1.-zdelta)+RLSTT*zdelta)*qsat0_w(j)/(Rv*Ts0_w(j)*Ts0_w(j))
421 ENDDO
422 !
423 QQ_x(1:knon) = 1./dqsatdT0_x(1:knon)
424 QQ_w(1:knon) = 1./dqsatdT0_w(1:knon)
425 QQ_b(1:knon) = sigw(1:knon)*QQ_w(1:knon) + sigx(1:knon)*QQ_x(1:knon)
426 dd_QQ(1:knon) = QQ_w(1:knon) - QQ_x(1:knon)
427 !
428 DO j=1,knon
429 !
430 ! Exchange coefficients computation
431 ! ---------------------------------
432 !
433 ! Wind factor (Warning : this is not valid when using land_surf_orchidee)
434 mod_wind_x = min_wind_speed+SQRT(ygustiness(j)+yu_x(j,1)**2+yv_x(j,1)**2)
435 mod_wind_w = min_wind_speed+SQRT(ygustiness(j)+yu_w(j,1)**2+yv_w(j,1)**2)
436 !
437 !! rho1 = ypplay(j,1)/(RD*yt(j,1))
438 rho1 = ypplay(j,1)/(RD*(yt_x(j,1) + sigw(j)*(yt_w(j,1)-yt_x(j,1))))
439 !
440 ! (w) and (x) Exchange coefficients
441 Kech_h_x(j) = ycdragh_x(j) * mod_wind_x * rho1
442 Kech_h_w(j) = ycdragh_w(j) * mod_wind_w * rho1
443 Kech_q_x(j) = ycdragq_x(j) * mod_wind_x * rho1
444 Kech_q_w(j) = ycdragq_w(j) * mod_wind_w * rho1
445 Kech_m_x(j) = ycdragm_x(j) * mod_wind_x * rho1
446 Kech_m_w(j) = ycdragm_w(j) * mod_wind_w * rho1
447 !! Print *,'YYYYpbl0: ycdragh_x, ycdragq_x, mod_wind_x, rho1, Kech_q_x, Kech_h_x ', &
448 !! ycdragh_x(j), ycdragq_x(j), mod_wind_x, rho1, Kech_q_x(j), Kech_h_x(j)
449 !! Print *,'YYYYpbl0: ycdragh_w, ycdragq_w, mod_wind_w, rho1, Kech_q_w, Kech_h_w ', &
450 !! ycdragh_w(j), ycdragq_w(j), mod_wind_w, rho1, Kech_q_w(j), Kech_h_w(j)
451 !
452 ! Merged exchange coefficients
453 dd_Kh = Kech_h_w(j) - Kech_h_x(j)
454 dd_Kq = Kech_q_w(j) - Kech_q_x(j)
455 dd_Km = Kech_m_w(j) - Kech_m_x(j)
456 IF (prt_level >=10) THEN
457 print *,' mod_wind_x, mod_wind_w ', mod_wind_x, mod_wind_w
458 print *,' rho1 ',rho1
459 print *,' ycdragh_x(j),ycdragm_x(j) ',ycdragh_x(j),ycdragm_x(j)
460 print *,' ycdragh_w(j),ycdragm_w(j) ',ycdragh_w(j),ycdragm_w(j)
461 print *,' dd_Kh: ',dd_Kh
462 ENDIF
463 !
464 Kech_h(j) = Kech_h_x(j) + sigw(j)*dd_Kh
465 Kech_q(j) = Kech_q_x(j) + sigw(j)*dd_Kq
466 Kech_m(j) = Kech_m_x(j) + sigw(j)*dd_Km
467 !
468 Kech_h_x_out(j) = Kech_h_x(j)
469 Kech_h_w_out(j) = Kech_h_w(j)
470 Kech_h_out(j) = Kech_h(j)
471 !
472 ! Effective exchange coefficient computation
473 ! ------------------------------------------
474 Kech_T_px(j) = Kech_h_x(j)/(1.-BcoefT_x(j)*Kech_h_x(j)*dtime)
475 Kech_T_pw(j) = Kech_h_w(j)/(1.-BcoefT_w(j)*Kech_h_w(j)*dtime)
476 !
477 Kech_Q_px(j) = Kech_q_x(j)/(1.-BcoefQ_x(j)*Kech_q_x(j)*dtime)
478 Kech_Q_pw(j) = Kech_q_w(j)/(1.-BcoefQ_w(j)*Kech_q_w(j)*dtime)
479 !
480 Kech_U_px(j) = Kech_m_x(j)/(1.-BcoefU_x(j)*Kech_m_x(j)*dtime)
481 Kech_U_pw(j) = Kech_m_w(j)/(1.-BcoefU_w(j)*Kech_m_w(j)*dtime)
482 !
483 Kech_V_px(j) = Kech_m_x(j)/(1.-BcoefV_x(j)*Kech_m_x(j)*dtime)
484 Kech_V_pw(j) = Kech_m_w(j)/(1.-BcoefV_w(j)*Kech_m_w(j)*dtime)
485 !
486 dd_KTp(j) = Kech_T_pw(j) - Kech_T_px(j)
487 dd_KQp(j) = Kech_Q_pw(j) - Kech_Q_px(j)
488 dd_KUp(j) = Kech_U_pw(j) - Kech_U_px(j)
489 dd_KVp(j) = Kech_V_pw(j) - Kech_V_px(j)
490 !
491 Kech_Tp(j) = Kech_T_px(j) + sigw(j)*dd_KTp(j)
492 Kech_Qp(j) = Kech_Q_px(j) + sigw(j)*dd_KQp(j)
493 Kech_Up(j) = Kech_U_px(j) + sigw(j)*dd_KUp(j)
494 Kech_Vp(j) = Kech_V_px(j) + sigw(j)*dd_KVp(j)
495 !
496 ! Store AQ and BQ in the module variables
497 AQ_x(j) = AcoefQ_x(j)
498 AQ_w(j) = AcoefQ_w(j)
499 BQ_x(j) = BcoefQ_x(j)
500 BQ_w(j) = BcoefQ_w(j)
501 !
502 ! Calcul des differences w-x
503 dd_Cdragm(j) = ycdragm_w(j) - ycdragm_x(j)
504 dd_Cdragh(j) = ycdragh_w(j) - ycdragh_x(j)
505 dd_Cdragq(j) = ycdragq_w(j) - ycdragq_x(j)
506 !
507 dd_AT(j) = AcoefT_w(j) - AcoefT_x(j)
508 dd_AQ(j) = AcoefQ_w(j) - AcoefQ_x(j)
509 dd_AU(j) = AcoefU_w(j) - AcoefU_x(j)
510 dd_AV(j) = AcoefV_w(j) - AcoefV_x(j)
511 dd_BT(j) = BcoefT_w(j) - BcoefT_x(j)
512 dd_BQ(j) = BcoefQ_w(j) - BcoefQ_x(j)
513 dd_BU(j) = BcoefU_w(j) - BcoefU_x(j)
514 dd_BV(j) = BcoefV_w(j) - BcoefV_x(j)
515 !
516 KxKwTp(j) = Kech_T_px(j)*Kech_T_pw(j)
517 KxKwQp(j) = Kech_Q_px(j)*Kech_Q_pw(j)
518 KxKwUp(j) = Kech_U_px(j)*Kech_U_pw(j)
519 KxKwVp(j) = Kech_V_px(j)*Kech_V_pw(j)
520 !
521 !
522 IF (prt_level >=10) THEN
523 print *,'Variables pour la fusion : Kech_T_px(j)' ,Kech_T_px(j)
524 print *,'Variables pour la fusion : Kech_T_pw(j)' ,Kech_T_pw(j)
525 print *,'Variables pour la fusion : Kech_Tp(j)' ,Kech_Tp(j)
526 print *,'Variables pour la fusion : Kech_h(j)' ,Kech_h(j)
527 ENDIF
528
529 ENDDO ! j = 1, knon
530
531 RETURN
532
533 END SUBROUTINE wx_pbl_prelim_0
534
535 SUBROUTINE wx_pbl_prelim_beta(knon, dtime, &
536 sigw, beta, &
537 BcoefQ_x, BcoefQ_w &
538 )
539 !
540 USE print_control_mod, ONLY: prt_level,lunout
541 USE indice_sol_mod, ONLY: is_oce
542 !
543 INTEGER, INTENT(IN) :: knon ! number of grid cells
544 REAL, INTENT(IN) :: dtime ! time step size (s)
545 REAL, DIMENSION(knon), INTENT(IN) :: sigw ! cold pools fractional area
546 REAL, DIMENSION(knon), INTENT(IN) :: beta ! evaporation by potential evaporation
547 REAL, DIMENSION(knon), INTENT(IN) :: BcoefQ_x, BcoefQ_w
548 !
549 ! Local variables
550 INTEGER :: j
551 !
552 DO j = 1, knon
553 !
554 qsatsrf0_x(j) = beta(j)*qsat0_x(j)
555 qsatsrf0_w(j) = beta(j)*qsat0_w(j)
556 dqsatsrf0(j) = qsatsrf0_w(j) - qsatsrf0_x(j)
557 !
558 Kech_Q_sx(j) = Kech_q_x(j)/(1.-beta(j)*BcoefQ_x(j)*Kech_q_x(j)*dtime)
559 Kech_Q_sw(j) = Kech_q_w(j)/(1.-beta(j)*BcoefQ_w(j)*Kech_q_w(j)*dtime)
560 !
561 dd_KQs(j) = Kech_Q_sw(j) - Kech_Q_sx(j)
562 !
563 Kech_Qs(j) = Kech_Q_sx(j) + sigw(j)*dd_KQs(j)
564 !
565 KxKwQs(j) = Kech_Q_sx(j)*Kech_Q_sw(j)
566 !
567 !! print *,'BBBBwx_prelim_beta : beta ', beta(j)
568 !
569 ENDDO ! j = 1, knon
570
571 RETURN
572
573 END SUBROUTINE wx_pbl_prelim_beta
574
575 1 SUBROUTINE wx_pbl_final
576 !
577 !****************************************************************************************
578 ! Deallocate module variables
579 !
580 !****************************************************************************************
581 !
582
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(C_p)) DEALLOCATE(C_p)
583
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(L_v)) DEALLOCATE(L_v)
584
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Ts0)) DEALLOCATE(Ts0)
585
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dTs0)) DEALLOCATE(dTs0)
586
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Ts0_x)) DEALLOCATE(Ts0_x)
587
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Ts0_w)) DEALLOCATE(Ts0_w)
588
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(qsat0)) DEALLOCATE(qsat0)
589
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dqsatdT0)) DEALLOCATE(dqsatdT0 )
590
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(qsat0_x)) DEALLOCATE(qsat0_x)
591
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dqsatdT0_x)) DEALLOCATE(dqsatdT0_x )
592
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(qsat0_w)) DEALLOCATE(qsat0_w)
593
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dqsatdT0_w)) DEALLOCATE(dqsatdT0_w )
594
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(q1_0b)) DEALLOCATE(q1_0b)
595
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(QQ_b)) DEALLOCATE(QQ_b)
596
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_QQ)) DEALLOCATE(dd_QQ)
597
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(QQ_x)) DEALLOCATE(QQ_x)
598
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(QQ_w)) DEALLOCATE(QQ_w)
599
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(qsatsrf0_x)) DEALLOCATE(qsatsrf0_x)
600
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(qsatsrf0_w)) DEALLOCATE(qsatsrf0_w)
601
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dqsatsrf0)) DEALLOCATE(dqsatsrf0)
602
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_Cdragh)) DEALLOCATE(dd_Cdragh)
603
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_Cdragm)) DEALLOCATE(dd_Cdragm)
604
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_Cdragq)) DEALLOCATE(dd_Cdragq)
605
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_h)) DEALLOCATE(Kech_h)
606
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_h_x)) DEALLOCATE(Kech_h_x)
607
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_h_w)) DEALLOCATE(Kech_h_w)
608
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_q)) DEALLOCATE(Kech_q)
609
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_q_x)) DEALLOCATE(Kech_q_x)
610
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_q_w)) DEALLOCATE(Kech_q_w)
611
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_m)) DEALLOCATE(Kech_m)
612
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_m_x)) DEALLOCATE(Kech_m_x)
613
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_m_w)) DEALLOCATE(Kech_m_w)
614
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_Tp)) DEALLOCATE(Kech_Tp)
615
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_T_px)) DEALLOCATE(Kech_T_px)
616
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_T_pw)) DEALLOCATE(Kech_T_pw)
617
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_KTp)) DEALLOCATE(dd_KTp)
618
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(KxKwTp)) DEALLOCATE(KxKwTp)
619
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_AT)) DEALLOCATE(dd_AT)
620
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_BT)) DEALLOCATE(dd_BT)
621
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_Qp)) DEALLOCATE(Kech_Qp)
622
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_Q_px)) DEALLOCATE(Kech_Q_px)
623
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_Q_pw)) DEALLOCATE(Kech_Q_pw)
624
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_KQp)) DEALLOCATE(dd_KQp)
625
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(KxKwQp)) DEALLOCATE(KxKwQp)
626
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_Qs)) DEALLOCATE(Kech_Qs)
627
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_Q_sx)) DEALLOCATE(Kech_Q_sx)
628
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_Q_sw)) DEALLOCATE(Kech_Q_sw)
629
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_KQs)) DEALLOCATE(dd_KQs)
630
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(KxKwQs )) DEALLOCATE(KxKwQs )
631
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(AQ_x)) DEALLOCATE(AQ_x)
632
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(AQ_w)) DEALLOCATE(AQ_w)
633
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(BQ_x)) DEALLOCATE(BQ_x)
634
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(BQ_w)) DEALLOCATE(BQ_w)
635
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_AQ)) DEALLOCATE(dd_AQ)
636
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_BQ )) DEALLOCATE(dd_BQ )
637
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_Up)) DEALLOCATE(Kech_Up)
638
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_U_px)) DEALLOCATE(Kech_U_px)
639
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_U_pw)) DEALLOCATE(Kech_U_pw)
640
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_KUp)) DEALLOCATE(dd_KUp)
641
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(KxKwUp)) DEALLOCATE(KxKwUp)
642
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_AU)) DEALLOCATE(dd_AU)
643
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_BU)) DEALLOCATE(dd_BU)
644
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_Vp)) DEALLOCATE(Kech_Vp)
645
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_V_px)) DEALLOCATE(Kech_V_px)
646
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(Kech_V_pw)) DEALLOCATE(Kech_V_pw)
647
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_KVp)) DEALLOCATE(dd_KVp)
648
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(KxKwVp)) DEALLOCATE(KxKwVp)
649
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_AV)) DEALLOCATE(dd_AV)
650
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ALLOCATED(dd_BV)) DEALLOCATE(dd_BV)
651
652 1 END SUBROUTINE wx_pbl_final
653
654 END MODULE wx_pbl_var_mod
655
656