source: palm/trunk/SOURCE/prandtl_fluxes.f90 @ 1276

Last change on this file since 1276 was 1276, checked in by heinze, 10 years ago

Usage of Dirichlet bottom boundary condition for scalars in conjunction with large scale forcing enabled

  • Property svn:keywords set to Id
File size: 15.3 KB
Line 
1 SUBROUTINE prandtl_fluxes
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! Use LSF_DATA also in case of Dirichlet bottom boundary condition for scalars
23!
24! Former revisions:
25! -----------------
26! $Id: prandtl_fluxes.f90 1276 2014-01-15 13:40:41Z heinze $
27!
28! 1257 2013-11-08 15:18:40Z raasch
29! openACC "kernels do" replaced by "kernels loop", "loop independent" added
30!
31! 1036 2012-10-22 13:43:42Z raasch
32! code put under GPL (PALM 3.9)
33!
34! 1015 2012-09-27 09:23:24Z raasch
35! OpenACC statements added
36!
37! 978 2012-08-09 08:28:32Z fricke
38! roughness length for scalar quantities z0h added
39!
40! 759 2011-09-15 13:58:31Z raasch
41! Bugfix for ts limitation
42!
43! 709 2011-03-30 09:31:40Z raasch
44! formatting adjustments
45!
46! 667 2010-12-23 12:06:00Z suehring/gryschka
47! Changed surface boundary conditions for u and v from mirror to Dirichlet.
48! Therefore u(uzb,:,:) and v(nzb,:,:) are now representative for height z0.
49! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
50!
51! 315 2009-05-13 10:57:59Z raasch
52! Saturation condition at (sea) surface is not used in precursor runs (only
53! in the following coupled runs)
54! Bugfix: qsws was calculated in case of constant heatflux = .FALSE.
55!
56! 187 2008-08-06 16:25:09Z letzel
57! Bugfix: modification of the calculation of the vertical turbulent momentum
58! fluxes u'w' and v'w'
59! Bugfix: change definition of us_wall from 1D to 2D
60! Change: modification of the integrated version of the profile function for
61! momentum for unstable stratification (does not effect results)
62!
63! 108 2007-08-24 15:10:38Z letzel
64! assume saturation at k=nzb_s_inner(j,i) for atmosphere coupled to ocean
65!
66! 75 2007-03-22 09:54:05Z raasch
67! moisture renamed humidity
68!
69! RCS Log replace by Id keyword, revision history cleaned up
70!
71! Revision 1.19  2006/04/26 12:24:35  raasch
72! +OpenMP directives and optimization (array assignments replaced by DO loops)
73!
74! Revision 1.1  1998/01/23 10:06:06  raasch
75! Initial revision
76!
77!
78! Description:
79! ------------
80! Diagnostic computation of vertical fluxes in the Prandtl layer from the
81! values of the variables at grid point k=1
82!------------------------------------------------------------------------------!
83
84    USE arrays_3d
85    USE control_parameters
86    USE grid_variables
87    USE indices
88
89    IMPLICIT NONE
90
91    INTEGER ::  i, j, k
92    LOGICAL ::  coupled_run
93    REAL    ::  a, b, e_q, rifm, uv_total, z_p
94
95!
96!-- Data information for accelerators
97    !$acc data present( e, nzb_u_inner, nzb_v_inner, nzb_s_inner, pt, q, qs ) &
98    !$acc      present( qsws, rif, shf, ts, u, us, usws, v, vpt, vsws, zu, zw, z0, z0h )
99!
100!-- Compute theta*
101    IF ( constant_heatflux )  THEN
102!
103!--    For a given heat flux in the Prandtl layer:
104!--    for u* use the value from the previous time step
105       !$OMP PARALLEL DO
106       !$acc kernels loop
107       DO  i = nxlg, nxrg
108          DO  j = nysg, nyng
109             ts(j,i) = -shf(j,i) / ( us(j,i) + 1E-30 )
110!
111!--          ts must be limited, because otherwise overflow may occur in case of
112!--          us=0 when computing rif further below
113             IF ( ts(j,i) < -1.05E5 )  ts(j,i) = -1.0E5
114             IF ( ts(j,i) >   1.0E5 )  ts(j,i) =  1.0E5
115          ENDDO
116       ENDDO
117
118    ELSE
119!
120!--    For a given surface temperature:
121!--    (the Richardson number is still the one from the previous time step)
122   
123       IF ( large_scale_forcing .AND. lsf_surf )  THEN
124          pt(0,:,:) = pt_surface
125       ENDIF
126
127       !$OMP PARALLEL DO PRIVATE( a, b, k, z_p )
128       !$acc kernels loop
129       DO  i = nxlg, nxrg
130          DO  j = nysg, nyng
131
132             k   = nzb_s_inner(j,i)
133             z_p = zu(k+1) - zw(k)
134
135             IF ( rif(j,i) >= 0.0 )  THEN
136!
137!--             Stable stratification
138                ts(j,i) = kappa * ( pt(k+1,j,i) - pt(k,j,i) ) / (           &
139                                  LOG( z_p / z0h(j,i) ) +                   &
140                                  5.0 * rif(j,i) * ( z_p - z0h(j,i) ) / z_p &
141                                                                )
142             ELSE
143!
144!--             Unstable stratification
145                a = SQRT( 1.0 - 16.0 * rif(j,i) )
146                b = SQRT( 1.0 - 16.0 * rif(j,i) * z0h(j,i) / z_p )
147
148                ts(j,i) = kappa * ( pt(k+1,j,i) - pt(k,j,i) ) /  (          &
149                          LOG( z_p / z0h(j,i) ) -                           &
150                          2.0 * LOG( ( 1.0 + a ) / ( 1.0 + b ) ) )
151             ENDIF
152
153          ENDDO
154       ENDDO
155    ENDIF
156
157!
158!-- Compute z_p/L (corresponds to the Richardson-flux number)
159    IF ( .NOT. humidity )  THEN
160       !$OMP PARALLEL DO PRIVATE( k, z_p )
161       !$acc kernels loop
162       DO  i = nxlg, nxrg
163          DO  j = nysg, nyng
164             k   = nzb_s_inner(j,i)
165             z_p = zu(k+1) - zw(k)
166             rif(j,i) = z_p * kappa * g * ts(j,i) / &
167                        ( pt(k+1,j,i) * ( us(j,i)**2 + 1E-30 ) )
168!
169!--          Limit the value range of the Richardson numbers.
170!--          This is necessary for very small velocities (u,v --> 0), because
171!--          the absolute value of rif can then become very large, which in
172!--          consequence would result in very large shear stresses and very
173!--          small momentum fluxes (both are generally unrealistic).
174             IF ( rif(j,i) < rif_min )  rif(j,i) = rif_min
175             IF ( rif(j,i) > rif_max )  rif(j,i) = rif_max
176          ENDDO
177       ENDDO
178    ELSE
179       !$OMP PARALLEL DO PRIVATE( k, z_p )
180       !$acc kernels loop
181       DO  i = nxlg, nxrg
182          DO  j = nysg, nyng
183             k   = nzb_s_inner(j,i)
184             z_p = zu(k+1) - zw(k)
185             rif(j,i) = z_p * kappa * g *                            &
186                        ( ts(j,i) + 0.61 * pt(k+1,j,i) * qs(j,i) ) / &
187                        ( vpt(k+1,j,i) * ( us(j,i)**2 + 1E-30 ) )
188!
189!--          Limit the value range of the Richardson numbers.
190!--          This is necessary for very small velocities (u,v --> 0), because
191!--          the absolute value of rif can then become very large, which in
192!--          consequence would result in very large shear stresses and very
193!--          small momentum fluxes (both are generally unrealistic).
194             IF ( rif(j,i) < rif_min )  rif(j,i) = rif_min
195             IF ( rif(j,i) > rif_max )  rif(j,i) = rif_max
196          ENDDO
197       ENDDO       
198    ENDIF
199
200!
201!-- Compute u* at the scalars' grid points
202    !$OMP PARALLEL DO PRIVATE( a, b, k, uv_total, z_p )
203    !$acc kernels loop
204    DO  i = nxl, nxr
205       DO  j = nys, nyn
206
207          k   = nzb_s_inner(j,i)
208          z_p = zu(k+1) - zw(k)
209
210!
211!--       Compute the absolute value of the horizontal velocity
212!--       (relative to the surface)
213          uv_total = SQRT( ( 0.5 * ( u(k+1,j,i) + u(k+1,j,i+1)        &
214                                   - u(k,j,i)   - u(k,j,i+1) ) )**2 + &
215                           ( 0.5 * ( v(k+1,j,i) + v(k+1,j+1,i)        &
216                                   - v(k,j,i)   - v(k,j+1,i) ) )**2 )   
217
218
219          IF ( rif(j,i) >= 0.0 )  THEN
220!
221!--          Stable stratification
222             us(j,i) = kappa * uv_total / (                                &
223                                  LOG( z_p / z0(j,i) ) +                   &
224                                  5.0 * rif(j,i) * ( z_p - z0(j,i) ) / z_p &
225                                          )
226          ELSE
227!
228!--          Unstable stratification
229             a = SQRT( SQRT( 1.0 - 16.0 * rif(j,i) ) )
230             b = SQRT( SQRT( 1.0 - 16.0 * rif(j,i) / z_p * z0(j,i) ) )
231
232             us(j,i) = kappa * uv_total / (                                  &
233                       LOG( z_p / z0(j,i) ) -                                &
234                       LOG( ( 1.0 + a )**2 * ( 1.0 + a**2 ) / (              &
235                            ( 1.0 + b )**2 * ( 1.0 + b**2 )   ) ) +          &
236                            2.0 * ( ATAN( a ) - ATAN( b ) )                  &
237                                           )
238          ENDIF
239       ENDDO
240    ENDDO
241
242!
243!-- Values of us at ghost point locations are needed for the evaluation of usws
244!-- and vsws.
245    !$acc update host( us )
246    CALL exchange_horiz_2d( us )
247    !$acc update device( us )
248
249!
250!-- Compute u'w' for the total model domain.
251!-- First compute the corresponding component of u* and square it.
252    !$OMP PARALLEL DO PRIVATE( a, b, k, rifm, z_p )
253    !$acc kernels loop
254    DO  i = nxl, nxr
255       DO  j = nys, nyn
256
257          k   = nzb_u_inner(j,i)
258          z_p = zu(k+1) - zw(k)
259
260!
261!--       Compute Richardson-flux number for this point
262          rifm = 0.5 * ( rif(j,i-1) + rif(j,i) )
263          IF ( rifm >= 0.0 )  THEN
264!
265!--          Stable stratification
266             usws(j,i) = kappa * ( u(k+1,j,i) - u(k,j,i) )/ (              &
267                                     LOG( z_p / z0(j,i) ) +               &
268                                     5.0 * rifm * ( z_p - z0(j,i) ) / z_p &
269                                              )
270          ELSE
271!
272!--          Unstable stratification
273             a = SQRT( SQRT( 1.0 - 16.0 * rifm ) )
274             b = SQRT( SQRT( 1.0 - 16.0 * rifm / z_p * z0(j,i) ) )
275
276             usws(j,i) = kappa * ( u(k+1,j,i) - u(k,j,i) ) / (            &
277                         LOG( z_p / z0(j,i) ) -                           &
278                         LOG( (1.0 + a )**2 * ( 1.0 + a**2 ) / (          &
279                              (1.0 + b )**2 * ( 1.0 + b**2 )   ) ) +      &
280                              2.0 * ( ATAN( a ) - ATAN( b ) )             &
281                                                 )
282          ENDIF
283          usws(j,i) = -usws(j,i) * 0.5 * ( us(j,i-1) + us(j,i) )
284       ENDDO
285    ENDDO
286
287!
288!-- Compute v'w' for the total model domain.
289!-- First compute the corresponding component of u* and square it.
290    !$OMP PARALLEL DO PRIVATE( a, b, k, rifm, z_p )
291    !$acc kernels loop
292    DO  i = nxl, nxr
293       DO  j = nys, nyn
294
295          k   = nzb_v_inner(j,i)
296          z_p = zu(k+1) - zw(k)
297
298!
299!--       Compute Richardson-flux number for this point
300          rifm = 0.5 * ( rif(j-1,i) + rif(j,i) )
301          IF ( rifm >= 0.0 )  THEN
302!
303!--          Stable stratification
304             vsws(j,i) = kappa * ( v(k+1,j,i) -  v(k,j,i) ) / (           &
305                                     LOG( z_p / z0(j,i) ) +               &
306                                     5.0 * rifm * ( z_p - z0(j,i) ) / z_p &
307                                              )
308          ELSE
309!
310!--          Unstable stratification
311             a = SQRT( SQRT( 1.0 - 16.0 * rifm ) )
312             b = SQRT( SQRT( 1.0 - 16.0 * rifm / z_p * z0(j,i) ) )
313
314             vsws(j,i) = kappa * ( v(k+1,j,i) - v(k,j,i) ) / (            &
315                         LOG( z_p / z0(j,i) ) -                           &
316                         LOG( (1.0 + a )**2 * ( 1.0 + a**2 ) / (          &
317                              (1.0 + b )**2 * ( 1.0 + b**2 )   ) ) +      &
318                              2.0 * ( ATAN( a ) - ATAN( b ) )             &
319                                                 )
320          ENDIF
321          vsws(j,i) = -vsws(j,i) * 0.5 * ( us(j-1,i) + us(j,i) )
322       ENDDO
323    ENDDO
324
325!
326!-- If required compute q*
327    IF ( humidity  .OR.  passive_scalar )  THEN
328       IF ( constant_waterflux )  THEN
329!
330!--       For a given water flux in the Prandtl layer:
331          !$OMP PARALLEL DO
332          !$acc kernels loop
333          DO  i = nxlg, nxrg
334             DO  j = nysg, nyng
335                qs(j,i) = -qsws(j,i) / ( us(j,i) + 1E-30 )
336             ENDDO
337          ENDDO
338         
339       ELSE
340          coupled_run = ( coupling_mode == 'atmosphere_to_ocean' .AND. run_coupled )
341
342           IF ( large_scale_forcing .AND. lsf_surf )  THEN
343              q(0,:,:) = q_surface
344           ENDIF
345
346          !$OMP PARALLEL DO PRIVATE( a, b, k, z_p )
347          !$acc kernels loop independent
348          DO  i = nxlg, nxrg
349             !$acc loop independent
350             DO  j = nysg, nyng
351
352                k   = nzb_s_inner(j,i)
353                z_p = zu(k+1) - zw(k)
354
355!
356!--             Assume saturation for atmosphere coupled to ocean (but not
357!--             in case of precursor runs)
358                IF ( coupled_run )  THEN
359                   e_q = 6.1 * &
360                        EXP( 0.07 * ( MIN(pt(0,j,i),pt(1,j,i)) - 273.15 ) )
361                   q(k,j,i) = 0.622 * e_q / ( surface_pressure - e_q )
362                ENDIF
363                IF ( rif(j,i) >= 0.0 )  THEN
364!
365!--                Stable stratification
366                   qs(j,i) = kappa * ( q(k+1,j,i) - q(k,j,i) ) / (          &
367                                  LOG( z_p / z0h(j,i) ) +                   &
368                                  5.0 * rif(j,i) * ( z_p - z0h(j,i) ) / z_p &
369                                                                 )
370                ELSE
371!
372!--                Unstable stratification
373                   a = SQRT( 1.0 - 16.0 * rif(j,i) ) 
374                   b = SQRT( 1.0 - 16.0 * rif(j,i) * z0h(j,i) / z_p ) 
375 
376                   qs(j,i) = kappa * ( q(k+1,j,i) - q(k,j,i) ) /   (        &
377                             LOG( z_p / z0h(j,i) ) -                        &
378                              2.0 * LOG( (1.0 + a ) / ( 1.0 + b ) ) )
379                ENDIF
380
381             ENDDO
382          ENDDO
383       ENDIF
384    ENDIF
385
386!
387!-- Exchange the boundaries for the momentum fluxes (only for sake of
388!-- completeness)
389    !$acc update host( usws, vsws )
390    CALL exchange_horiz_2d( usws )
391    CALL exchange_horiz_2d( vsws )
392    !$acc update device( usws, vsws )
393    IF ( humidity  .OR.  passive_scalar )  THEN
394       !$acc update host( qsws )
395       CALL exchange_horiz_2d( qsws )
396       !$acc update device( qsws )
397    ENDIF
398
399!
400!-- Compute the vertical kinematic heat flux
401    IF ( .NOT. constant_heatflux )  THEN
402       !$OMP PARALLEL DO
403       !$acc kernels loop independent
404       DO  i = nxlg, nxrg
405          !$acc loop independent
406          DO  j = nysg, nyng
407             shf(j,i) = -ts(j,i) * us(j,i)
408          ENDDO
409       ENDDO
410    ENDIF
411
412!
413!-- Compute the vertical water/scalar flux
414    IF ( .NOT. constant_waterflux .AND. ( humidity .OR. passive_scalar ) ) THEN
415       !$OMP PARALLEL DO
416       !$acc kernels loop independent
417       DO  i = nxlg, nxrg
418          !$acc loop independent
419          DO  j = nysg, nyng
420             qsws(j,i) = -qs(j,i) * us(j,i)
421          ENDDO
422       ENDDO
423    ENDIF
424
425!
426!-- Bottom boundary condition for the TKE
427    IF ( ibc_e_b == 2 )  THEN
428       !$OMP PARALLEL DO
429       !$acc kernels loop independent
430       DO  i = nxlg, nxrg
431          !$acc loop independent
432          DO  j = nysg, nyng
433             e(nzb_s_inner(j,i)+1,j,i) = ( us(j,i) / 0.1 )**2
434!
435!--          As a test: cm = 0.4
436!            e(nzb_s_inner(j,i)+1,j,i) = ( us(j,i) / 0.4 )**2
437             e(nzb_s_inner(j,i),j,i)   = e(nzb_s_inner(j,i)+1,j,i)
438          ENDDO
439       ENDDO
440    ENDIF
441
442    !$acc end data
443
444 END SUBROUTINE prandtl_fluxes
Note: See TracBrowser for help on using the repository browser.