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

Last change on this file since 709 was 709, checked in by raasch, 13 years ago

formatting adjustments

  • Property svn:keywords set to Id
File size: 12.8 KB
RevLine 
[1]1 SUBROUTINE prandtl_fluxes
2
3!------------------------------------------------------------------------------!
[484]4! Current revisions:
[1]5! -----------------
[709]6! formatting adjustments
[1]7!
[668]8! Former revisions:
9! -----------------
10! $Id: prandtl_fluxes.f90 709 2011-03-30 09:31:40Z raasch $
11!
12! 667 2010-12-23 12:06:00Z suehring/gryschka
[709]13! Changed surface boundary conditions for u and v from mirror to Dirichlet.
14! Therefore u(uzb,:,:) and v(nzb,:,:) are now representative for height z0.
[667]15! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
16!
[392]17! 315 2009-05-13 10:57:59Z raasch
18! Saturation condition at (sea) surface is not used in precursor runs (only
19! in the following coupled runs)
20! Bugfix: qsws was calculated in case of constant heatflux = .FALSE.
21!
[198]22! 187 2008-08-06 16:25:09Z letzel
23! Bugfix: modification of the calculation of the vertical turbulent momentum
24! fluxes u'w' and v'w'
25! Bugfix: change definition of us_wall from 1D to 2D
26! Change: modification of the integrated version of the profile function for
27! momentum for unstable stratification (does not effect results)
28!
[110]29! 108 2007-08-24 15:10:38Z letzel
30! assume saturation at k=nzb_s_inner(j,i) for atmosphere coupled to ocean
31!
[77]32! 75 2007-03-22 09:54:05Z raasch
33! moisture renamed humidity
34!
[3]35! RCS Log replace by Id keyword, revision history cleaned up
36!
[1]37! Revision 1.19  2006/04/26 12:24:35  raasch
38! +OpenMP directives and optimization (array assignments replaced by DO loops)
39!
40! Revision 1.1  1998/01/23 10:06:06  raasch
41! Initial revision
42!
43!
44! Description:
45! ------------
46! Diagnostic computation of vertical fluxes in the Prandtl layer from the
47! values of the variables at grid point k=1
48!------------------------------------------------------------------------------!
49
50    USE arrays_3d
51    USE control_parameters
52    USE grid_variables
53    USE indices
54
55    IMPLICIT NONE
56
57    INTEGER ::  i, j, k
[108]58    REAL    ::  a, b, e_q, rifm, uv_total, z_p
[1]59
[667]60!
[1]61!-- Compute theta*
62    IF ( constant_heatflux )  THEN
63!
64!--    For a given heat flux in the Prandtl layer:
65!--    for u* use the value from the previous time step
66       !$OMP PARALLEL DO
[667]67       DO  i = nxlg, nxrg
68          DO  j = nysg, nyng
[1]69             ts(j,i) = -shf(j,i) / ( us(j,i) + 1E-30 )
70!
71!--          ts must be limited, because otherwise overflow may occur in case of
72!--          us=0 when computing rif further below
73             IF ( ts(j,i) < -1.05E5 )  ts = -1.0E5
74             IF ( ts(j,i) >   1.0E5 )  ts =  1.0E5
75          ENDDO
76       ENDDO
77
78    ELSE
79!
80!--    For a given surface temperature:
81!--    (the Richardson number is still the one from the previous time step)
82       !$OMP PARALLEL DO PRIVATE( a, b, k, z_p )
[667]83       DO  i = nxlg, nxrg
84          DO  j = nysg, nyng
[1]85
86             k   = nzb_s_inner(j,i)
87             z_p = zu(k+1) - zw(k)
88
89             IF ( rif(j,i) >= 0.0 )  THEN
90!
91!--             Stable stratification
92                ts(j,i) = kappa * ( pt(k+1,j,i) - pt(k,j,i) ) / (          &
93                                  LOG( z_p / z0(j,i) ) +                   &
94                                  5.0 * rif(j,i) * ( z_p - z0(j,i) ) / z_p &
95                                                                )
96             ELSE
97!
98!--             Unstable stratification
99                a = SQRT( 1.0 - 16.0 * rif(j,i) )
[187]100                b = SQRT( 1.0 - 16.0 * rif(j,i) * z0(j,i) / z_p )
101
102                ts(j,i) = kappa * ( pt(k+1,j,i) - pt(k,j,i) ) /  (         &
103                          LOG( z_p / z0(j,i) ) -                           &
104                          2.0 * LOG( ( 1.0 + a ) / ( 1.0 + b ) ) )
[1]105             ENDIF
106
107          ENDDO
108       ENDDO
109    ENDIF
110
111!
112!-- Compute z_p/L (corresponds to the Richardson-flux number)
[75]113    IF ( .NOT. humidity )  THEN
[1]114       !$OMP PARALLEL DO PRIVATE( k, z_p )
[667]115       DO  i = nxlg, nxrg
116          DO  j = nysg, nyng
[1]117             k   = nzb_s_inner(j,i)
118             z_p = zu(k+1) - zw(k)
119             rif(j,i) = z_p * kappa * g * ts(j,i) / &
120                        ( pt(k+1,j,i) * ( us(j,i)**2 + 1E-30 ) )
121!
122!--          Limit the value range of the Richardson numbers.
123!--          This is necessary for very small velocities (u,v --> 0), because
124!--          the absolute value of rif can then become very large, which in
125!--          consequence would result in very large shear stresses and very
126!--          small momentum fluxes (both are generally unrealistic).
127             IF ( rif(j,i) < rif_min )  rif(j,i) = rif_min
128             IF ( rif(j,i) > rif_max )  rif(j,i) = rif_max
129          ENDDO
130       ENDDO
131    ELSE
132       !$OMP PARALLEL DO PRIVATE( k, z_p )
[667]133       DO  i = nxlg, nxrg
134          DO  j = nysg, nyng
[1]135             k   = nzb_s_inner(j,i)
136             z_p = zu(k+1) - zw(k)
137             rif(j,i) = z_p * kappa * g *                            &
138                        ( ts(j,i) + 0.61 * pt(k+1,j,i) * qs(j,i) ) / &
139                        ( vpt(k+1,j,i) * ( us(j,i)**2 + 1E-30 ) )
140!
141!--          Limit the value range of the Richardson numbers.
142!--          This is necessary for very small velocities (u,v --> 0), because
143!--          the absolute value of rif can then become very large, which in
144!--          consequence would result in very large shear stresses and very
145!--          small momentum fluxes (both are generally unrealistic).
146             IF ( rif(j,i) < rif_min )  rif(j,i) = rif_min
147             IF ( rif(j,i) > rif_max )  rif(j,i) = rif_max
148          ENDDO
149       ENDDO       
150    ENDIF
151
152!
153!-- Compute u* at the scalars' grid points
154    !$OMP PARALLEL DO PRIVATE( a, b, k, uv_total, z_p )
155    DO  i = nxl, nxr
156       DO  j = nys, nyn
157
158          k   = nzb_s_inner(j,i)
159          z_p = zu(k+1) - zw(k)
160
161!
[667]162!--       Compute the absolute value of the horizontal velocity
163!--       (relative to the surface)
164          uv_total = SQRT( ( 0.5 * ( u(k+1,j,i) + u(k+1,j,i+1)        &
165                                   - u(k,j,i)   - u(k,j,i+1) ) )**2 + &
166                           ( 0.5 * ( v(k+1,j,i) + v(k+1,j+1,i)        &
167                                   - v(k,j,i)   - v(k,j+1,i) ) )**2 )   
[1]168
[667]169
[1]170          IF ( rif(j,i) >= 0.0 )  THEN
171!
172!--          Stable stratification
173             us(j,i) = kappa * uv_total / (                                &
174                                  LOG( z_p / z0(j,i) ) +                   &
175                                  5.0 * rif(j,i) * ( z_p - z0(j,i) ) / z_p &
176                                          )
177          ELSE
178!
179!--          Unstable stratification
[187]180             a = SQRT( SQRT( 1.0 - 16.0 * rif(j,i) ) )
181             b = SQRT( SQRT( 1.0 - 16.0 * rif(j,i) / z_p * z0(j,i) ) )
182
183             us(j,i) = kappa * uv_total / (                                  &
184                       LOG( z_p / z0(j,i) ) -                                &
185                       LOG( ( 1.0 + a )**2 * ( 1.0 + a**2 ) / (              &
186                            ( 1.0 + b )**2 * ( 1.0 + b**2 )   ) ) +          &
187                            2.0 * ( ATAN( a ) - ATAN( b ) )                  &
188                                           )
[1]189          ENDIF
190       ENDDO
191    ENDDO
192
193!
[187]194!-- Values of us at ghost point locations are needed for the evaluation of usws
195!-- and vsws.
196    CALL exchange_horiz_2d( us )
197!
[1]198!-- Compute u'w' for the total model domain.
199!-- First compute the corresponding component of u* and square it.
200    !$OMP PARALLEL DO PRIVATE( a, b, k, rifm, z_p )
201    DO  i = nxl, nxr
202       DO  j = nys, nyn
203
204          k   = nzb_u_inner(j,i)
205          z_p = zu(k+1) - zw(k)
206
207!
208!--       Compute Richardson-flux number for this point
209          rifm = 0.5 * ( rif(j,i-1) + rif(j,i) )
210          IF ( rifm >= 0.0 )  THEN
211!
212!--          Stable stratification
[667]213             usws(j,i) = kappa * ( u(k+1,j,i) - u(k,j,i) )/ (              &
[1]214                                     LOG( z_p / z0(j,i) ) +               &
215                                     5.0 * rifm * ( z_p - z0(j,i) ) / z_p &
216                                              )
217          ELSE
218!
219!--          Unstable stratification
[187]220             a = SQRT( SQRT( 1.0 - 16.0 * rifm ) )
221             b = SQRT( SQRT( 1.0 - 16.0 * rifm / z_p * z0(j,i) ) )
222
[667]223             usws(j,i) = kappa * ( u(k+1,j,i) - u(k,j,i) ) / (            &
[187]224                         LOG( z_p / z0(j,i) ) -                           &
225                         LOG( (1.0 + a )**2 * ( 1.0 + a**2 ) / (          &
226                              (1.0 + b )**2 * ( 1.0 + b**2 )   ) ) +      &
227                              2.0 * ( ATAN( a ) - ATAN( b ) )             &
[1]228                                                 )
229          ENDIF
[187]230          usws(j,i) = -usws(j,i) * 0.5 * ( us(j,i-1) + us(j,i) )
[1]231       ENDDO
232    ENDDO
233
234!
235!-- Compute v'w' for the total model domain.
236!-- First compute the corresponding component of u* and square it.
237    !$OMP PARALLEL DO PRIVATE( a, b, k, rifm, z_p )
238    DO  i = nxl, nxr
239       DO  j = nys, nyn
240
241          k   = nzb_v_inner(j,i)
242          z_p = zu(k+1) - zw(k)
243
244!
245!--       Compute Richardson-flux number for this point
246          rifm = 0.5 * ( rif(j-1,i) + rif(j,i) )
247          IF ( rifm >= 0.0 )  THEN
248!
249!--          Stable stratification
[667]250             vsws(j,i) = kappa * ( v(k+1,j,i) -  v(k,j,i) ) / (           &
[1]251                                     LOG( z_p / z0(j,i) ) +               &
252                                     5.0 * rifm * ( z_p - z0(j,i) ) / z_p &
253                                              )
254          ELSE
255!
256!--          Unstable stratification
[187]257             a = SQRT( SQRT( 1.0 - 16.0 * rifm ) )
258             b = SQRT( SQRT( 1.0 - 16.0 * rifm / z_p * z0(j,i) ) )
259
[667]260             vsws(j,i) = kappa * ( v(k+1,j,i) - v(k,j,i) ) / (            &
[187]261                         LOG( z_p / z0(j,i) ) -                           &
262                         LOG( (1.0 + a )**2 * ( 1.0 + a**2 ) / (          &
263                              (1.0 + b )**2 * ( 1.0 + b**2 )   ) ) +      &
264                              2.0 * ( ATAN( a ) - ATAN( b ) )             &
[1]265                                                 )
266          ENDIF
[187]267          vsws(j,i) = -vsws(j,i) * 0.5 * ( us(j-1,i) + us(j,i) )
[1]268       ENDDO
269    ENDDO
270
271!
272!-- If required compute q*
[75]273    IF ( humidity  .OR.  passive_scalar )  THEN
[1]274       IF ( constant_waterflux )  THEN
275!
276!--       For a given water flux in the Prandtl layer:
277          !$OMP PARALLEL DO
[667]278          DO  i = nxlg, nxrg
279             DO  j = nysg, nyng
[1]280                qs(j,i) = -qsws(j,i) / ( us(j,i) + 1E-30 )
281             ENDDO
282          ENDDO
283         
284       ELSE         
285          !$OMP PARALLEL DO PRIVATE( a, b, k, z_p )
[667]286          DO  i = nxlg, nxrg
287             DO  j = nysg, nyng
[1]288
289                k   = nzb_s_inner(j,i)
290                z_p = zu(k+1) - zw(k)
291
[108]292!
[291]293!--             Assume saturation for atmosphere coupled to ocean (but not
294!--             in case of precursor runs)
295                IF ( coupling_mode == 'atmosphere_to_ocean' .AND. run_coupled )&
296                THEN
[108]297                   e_q = 6.1 * &
298                        EXP( 0.07 * ( MIN(pt(0,j,i),pt(1,j,i)) - 273.15 ) )
299                   q(k,j,i) = 0.622 * e_q / ( surface_pressure - e_q )
300                ENDIF
[1]301                IF ( rif(j,i) >= 0.0 )  THEN
302!
303!--                Stable stratification
304                   qs(j,i) = kappa * ( q(k+1,j,i) - q(k,j,i) ) / (         &
305                                  LOG( z_p / z0(j,i) ) +                   &
306                                  5.0 * rif(j,i) * ( z_p - z0(j,i) ) / z_p &
307                                                                 )
308                ELSE
309!
310!--                Unstable stratification
[187]311                   a = SQRT( 1.0 - 16.0 * rif(j,i) ) 
312                   b = SQRT( 1.0 - 16.0 * rif(j,i) * z0(j,i) / z_p ) 
313 
314                   qs(j,i) = kappa * ( q(k+1,j,i) - q(k,j,i) ) /   (   &
315                             LOG( z_p / z0(j,i) ) -                    &
316                              2.0 * LOG( (1.0 + a ) / ( 1.0 + b ) ) )
[1]317                ENDIF
318
319             ENDDO
320          ENDDO
321       ENDIF
322    ENDIF
323
324!
[187]325!-- Exchange the boundaries for the momentum fluxes (only for sake of
326!-- completeness)
[1]327    CALL exchange_horiz_2d( usws )
328    CALL exchange_horiz_2d( vsws )
[75]329    IF ( humidity  .OR.  passive_scalar )  CALL exchange_horiz_2d( qsws )
[1]330
331!
332!-- Compute the vertical kinematic heat flux
333    IF ( .NOT. constant_heatflux )  THEN
334       !$OMP PARALLEL DO
[667]335       DO  i = nxlg, nxrg
336          DO  j = nysg, nyng
[1]337             shf(j,i) = -ts(j,i) * us(j,i)
338          ENDDO
339       ENDDO
340    ENDIF
341
342!
343!-- Compute the vertical water/scalar flux
[315]344    IF ( .NOT. constant_waterflux .AND. ( humidity .OR. passive_scalar ) ) THEN
[1]345       !$OMP PARALLEL DO
[667]346       DO  i = nxlg, nxrg
347          DO  j = nysg, nyng
[1]348             qsws(j,i) = -qs(j,i) * us(j,i)
349          ENDDO
350       ENDDO
351    ENDIF
352
353!
354!-- Bottom boundary condition for the TKE
355    IF ( ibc_e_b == 2 )  THEN
356       !$OMP PARALLEL DO
[667]357       DO  i = nxlg, nxrg
358          DO  j = nysg, nyng
[1]359             e(nzb_s_inner(j,i)+1,j,i) = ( us(j,i) / 0.1 )**2
360!
361!--          As a test: cm = 0.4
362!            e(nzb_s_inner(j,i)+1,j,i) = ( us(j,i) / 0.4 )**2
363             e(nzb_s_inner(j,i),j,i)   = e(nzb_s_inner(j,i)+1,j,i)
364          ENDDO
365       ENDDO
366    ENDIF
367
368
369 END SUBROUTINE prandtl_fluxes
Note: See TracBrowser for help on using the repository browser.