source: palm/trunk/SOURCE/init_1d_model.f90 @ 1015

Last change on this file since 1015 was 1015, checked in by raasch, 12 years ago

Starting with changes required for GPU optimization. OpenACC statements for using NVIDIA GPUs added.
Adjustment of mixing length to the Prandtl mixing length at first grid point above ground removed.
mask array is set zero for ghost boundaries

  • Property svn:keywords set to Id
File size: 29.7 KB
Line 
1 SUBROUTINE init_1d_model
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! adjustment of mixing length to the Prandtl mixing length at first grid point
7! above ground removed
8!
9! Former revisions:
10! -----------------
11! $Id: init_1d_model.f90 1015 2012-09-27 09:23:24Z raasch $
12!
13! 1001 2012-09-13 14:08:46Z raasch
14! all actions concerning leapfrog scheme removed
15!
16! 996 2012-09-07 10:41:47Z raasch
17! little reformatting
18!
19! 978 2012-08-09 08:28:32Z fricke
20! roughness length for scalar quantities z0h1d added
21!
22! 667 2010-12-23 12:06:00Z suehring/gryschka
23! replaced mirror boundary conditions for u and v  at the ground
24! by dirichlet boundary conditions
25!
26! 254 2009-03-05 15:33:42Z heinze
27! Output of messages replaced by message handling routine.
28!
29! 184 2008-08-04 15:53:39Z letzel
30! provisional solution for run_control_1d output: add 'CALL check_open( 15 )'
31!
32! 135 2007-11-22 12:24:23Z raasch
33! Bugfix: absolute value of f must be used when calculating the Blackadar
34! mixing length
35!
36! 82 2007-04-16 15:40:52Z raasch
37! Preprocessor strings for different linux clusters changed to "lc",
38! routine local_flush is used for buffer flushing
39!
40! 75 2007-03-22 09:54:05Z raasch
41! Bugfix: preset of tendencies te_em, te_um, te_vm,
42! moisture renamed humidity
43!
44! RCS Log replace by Id keyword, revision history cleaned up
45!
46! Revision 1.21  2006/06/02 15:19:57  raasch
47! cpp-directives extended for lctit
48!
49! Revision 1.1  1998/03/09 16:22:10  raasch
50! Initial revision
51!
52!
53! Description:
54! ------------
55! 1D-model to initialize the 3D-arrays.
56! The temperature profile is set as steady and a corresponding steady solution
57! of the wind profile is being computed.
58! All subroutines required can be found within this file.
59!------------------------------------------------------------------------------!
60
61    USE arrays_3d
62    USE indices
63    USE model_1d
64    USE control_parameters
65
66    IMPLICIT NONE
67
68    CHARACTER (LEN=9) ::  time_to_string
69    INTEGER ::  k
70    REAL    ::  lambda
71
72!
73!-- Allocate required 1D-arrays
74    ALLOCATE( e1d(nzb:nzt+1),    e1d_p(nzb:nzt+1), &
75              kh1d(nzb:nzt+1),   km1d(nzb:nzt+1),  &
76              l_black(nzb:nzt+1), l1d(nzb:nzt+1),   &
77              rif1d(nzb:nzt+1),   te_e(nzb:nzt+1),  &
78              te_em(nzb:nzt+1),  te_u(nzb:nzt+1),    te_um(nzb:nzt+1), &
79              te_v(nzb:nzt+1),   te_vm(nzb:nzt+1),    u1d(nzb:nzt+1),   &
80              u1d_p(nzb:nzt+1),  v1d(nzb:nzt+1),   &
81              v1d_p(nzb:nzt+1) )
82
83!
84!-- Initialize arrays
85    IF ( constant_diffusion )  THEN
86       km1d = km_constant
87       kh1d = km_constant / prandtl_number
88    ELSE
89       e1d = 0.0; e1d_p = 0.0
90       kh1d = 0.0; km1d = 0.0
91       rif1d = 0.0
92!
93!--    Compute the mixing length
94       l_black(nzb) = 0.0
95
96       IF ( TRIM( mixing_length_1d ) == 'blackadar' )  THEN
97!
98!--       Blackadar mixing length
99          IF ( f /= 0.0 )  THEN
100             lambda = 2.7E-4 * SQRT( ug(nzt+1)**2 + vg(nzt+1)**2 ) / &
101                               ABS( f ) + 1E-10
102          ELSE
103             lambda = 30.0
104          ENDIF
105
106          DO  k = nzb+1, nzt+1
107             l_black(k) = kappa * zu(k) / ( 1.0 + kappa * zu(k) / lambda )
108          ENDDO
109
110       ELSEIF ( TRIM( mixing_length_1d ) == 'as_in_3d_model' )  THEN
111!
112!--       Use the same mixing length as in 3D model
113          l_black(1:nzt) = l_grid
114          l_black(nzt+1) = l_black(nzt)
115
116       ENDIF
117    ENDIF
118    l1d   = l_black
119    u1d   = u_init
120    u1d_p = u_init
121    v1d   = v_init
122    v1d_p = v_init
123
124!
125!-- Set initial horizontal velocities at the lowest grid levels to a very small
126!-- value in order to avoid too small time steps caused by the diffusion limit
127!-- in the initial phase of a run (at k=1, dz/2 occurs in the limiting formula!)
128    u1d(0:1)   = 0.1
129    u1d_p(0:1) = 0.1
130    v1d(0:1)   = 0.1
131    v1d_p(0:1) = 0.1
132
133!
134!-- For u*, theta* and the momentum fluxes plausible values are set
135    IF ( prandtl_layer )  THEN
136       us1d = 0.1   ! without initial friction the flow would not change
137    ELSE
138       e1d(nzb+1)  = 1.0
139       km1d(nzb+1) = 1.0
140       us1d = 0.0
141    ENDIF
142    ts1d = 0.0
143    usws1d = 0.0
144    vsws1d = 0.0
145    z01d  = roughness_length
146    z0h1d = z0h_factor * z01d 
147    IF ( humidity .OR. passive_scalar )  qs1d = 0.0
148
149!
150!-- Tendencies must be preset in order to avoid runtime errors within the
151!-- first Runge-Kutta step
152    te_em = 0.0
153    te_um = 0.0
154    te_vm = 0.0
155
156!
157!-- Set start time in hh:mm:ss - format
158    simulated_time_chr = time_to_string( simulated_time_1d )
159
160!
161!-- Integrate the 1D-model equations using the leap-frog scheme
162    CALL time_integration_1d
163
164
165 END SUBROUTINE init_1d_model
166
167
168
169 SUBROUTINE time_integration_1d
170
171!------------------------------------------------------------------------------!
172! Description:
173! ------------
174! Leap-frog time differencing scheme for the 1D-model.
175!------------------------------------------------------------------------------!
176
177    USE arrays_3d
178    USE control_parameters
179    USE indices
180    USE model_1d
181    USE pegrid
182
183    IMPLICIT NONE
184
185    CHARACTER (LEN=9) ::  time_to_string
186    INTEGER ::  k
187    REAL    ::  a, b, dissipation, dpt_dz, flux, kmzm, kmzp, l_stable, pt_0, &
188                uv_total
189
190!
191!-- Determine the time step at the start of a 1D-simulation and
192!-- determine and printout quantities used for run control
193    CALL timestep_1d
194    CALL run_control_1d
195
196!
197!-- Start of time loop
198    DO  WHILE ( simulated_time_1d < end_time_1d  .AND.  .NOT. stop_dt_1d )
199
200!
201!--    Depending on the timestep scheme, carry out one or more intermediate
202!--    timesteps
203
204       intermediate_timestep_count = 0
205       DO  WHILE ( intermediate_timestep_count < &
206                   intermediate_timestep_count_max )
207
208          intermediate_timestep_count = intermediate_timestep_count + 1
209
210          CALL timestep_scheme_steering
211
212!
213!--       Compute all tendency terms. If a Prandtl-layer is simulated, k starts
214!--       at nzb+2.
215          DO  k = nzb_diff, nzt
216
217             kmzm = 0.5 * ( km1d(k-1) + km1d(k) )
218             kmzp = 0.5 * ( km1d(k) + km1d(k+1) )
219!
220!--          u-component
221             te_u(k) =  f * ( v1d(k) - vg(k) ) + ( &
222                              kmzp * ( u1d(k+1) - u1d(k) ) * ddzu(k+1) &
223                            - kmzm * ( u1d(k) - u1d(k-1) ) * ddzu(k)   &
224                                                 ) * ddzw(k)
225!
226!--          v-component
227             te_v(k) = -f * ( u1d(k) - ug(k) ) + (                     &
228                              kmzp * ( v1d(k+1) - v1d(k) ) * ddzu(k+1) &
229                            - kmzm * ( v1d(k) - v1d(k-1) ) * ddzu(k)   &
230                                                 ) * ddzw(k)
231          ENDDO
232          IF ( .NOT. constant_diffusion )  THEN
233             DO  k = nzb_diff, nzt
234!
235!--             TKE
236                kmzm = 0.5 * ( km1d(k-1) + km1d(k) )
237                kmzp = 0.5 * ( km1d(k) + km1d(k+1) )
238                IF ( .NOT. humidity )  THEN
239                   pt_0 = pt_init(k)
240                   flux =  ( pt_init(k+1)-pt_init(k-1) ) * dd2zu(k)
241                ELSE
242                   pt_0 = pt_init(k) * ( 1.0 + 0.61 * q_init(k) )
243                   flux = ( ( pt_init(k+1) - pt_init(k-1) ) +                 &
244                            0.61 * pt_init(k) * ( q_init(k+1) - q_init(k-1) ) &
245                          ) * dd2zu(k)
246                ENDIF
247
248                IF ( dissipation_1d == 'detering' )  THEN
249!
250!--                According to Detering, c_e=0.064
251                   dissipation = 0.064 * e1d(k) * SQRT( e1d(k) ) / l1d(k)
252                ELSEIF ( dissipation_1d == 'as_in_3d_model' )  THEN
253                   dissipation = ( 0.19 + 0.74 * l1d(k) / l_grid(k) ) &
254                                 * e1d(k) * SQRT( e1d(k) ) / l1d(k)
255                ENDIF
256
257                te_e(k) = km1d(k) * ( ( ( u1d(k+1) - u1d(k-1) ) * dd2zu(k) )**2&
258                                    + ( ( v1d(k+1) - v1d(k-1) ) * dd2zu(k) )**2&
259                                    )                                          &
260                                    - g / pt_0 * kh1d(k) * flux                &
261                                    +            (                             &
262                                     kmzp * ( e1d(k+1) - e1d(k) ) * ddzu(k+1)  &
263                                   - kmzm * ( e1d(k) - e1d(k-1) ) * ddzu(k)    &
264                                                 ) * ddzw(k)                   &
265                                   - dissipation
266             ENDDO
267          ENDIF
268
269!
270!--       Tendency terms at the top of the Prandtl-layer.
271!--       Finite differences of the momentum fluxes are computed using half the
272!--       normal grid length (2.0*ddzw(k)) for the sake of enhanced accuracy
273          IF ( prandtl_layer )  THEN
274
275             k = nzb+1
276             kmzm = 0.5 * ( km1d(k-1) + km1d(k) )
277             kmzp = 0.5 * ( km1d(k) + km1d(k+1) )
278             IF ( .NOT. humidity )  THEN
279                pt_0 = pt_init(k)
280                flux =  ( pt_init(k+1)-pt_init(k-1) ) * dd2zu(k)
281             ELSE
282                pt_0 = pt_init(k) * ( 1.0 + 0.61 * q_init(k) )
283                flux = ( ( pt_init(k+1) - pt_init(k-1) ) +                 &
284                         0.61 * pt_init(k) * ( q_init(k+1) - q_init(k-1) ) &
285                       ) * dd2zu(k)
286             ENDIF
287
288             IF ( dissipation_1d == 'detering' )  THEN
289!
290!--             According to Detering, c_e=0.064
291                dissipation = 0.064 * e1d(k) * SQRT( e1d(k) ) / l1d(k)
292             ELSEIF ( dissipation_1d == 'as_in_3d_model' )  THEN
293                dissipation = ( 0.19 + 0.74 * l1d(k) / l_grid(k) ) &
294                              * e1d(k) * SQRT( e1d(k) ) / l1d(k)
295             ENDIF
296
297!
298!--          u-component
299             te_u(k) = f * ( v1d(k) - vg(k) ) + (                              &
300                       kmzp * ( u1d(k+1) - u1d(k) ) * ddzu(k+1) + usws1d       &
301                                                ) * 2.0 * ddzw(k)
302!
303!--          v-component
304             te_v(k) = -f * ( u1d(k) - ug(k) ) + (                             &
305                       kmzp * ( v1d(k+1) - v1d(k) ) * ddzu(k+1) + vsws1d       &
306                                                 ) * 2.0 * ddzw(k)
307!
308!--          TKE
309             te_e(k) = km1d(k) * ( ( ( u1d(k+1) - u1d(k-1) ) * dd2zu(k) )**2   &
310                                 + ( ( v1d(k+1) - v1d(k-1) ) * dd2zu(k) )**2   &
311                                 )                                             &
312                                 - g / pt_0 * kh1d(k) * flux                   &
313                                 +           (                                 &
314                                  kmzp * ( e1d(k+1) - e1d(k) ) * ddzu(k+1)     &
315                                - kmzm * ( e1d(k) - e1d(k-1) ) * ddzu(k)       &
316                                              ) * ddzw(k)                      &
317                                - dissipation
318          ENDIF
319
320!
321!--       Prognostic equations for all 1D variables
322          DO  k = nzb+1, nzt
323
324             u1d_p(k) = u1d(k) + dt_1d * ( tsc(2) * te_u(k) + &
325                                           tsc(3) * te_um(k) )
326             v1d_p(k) = v1d(k) + dt_1d * ( tsc(2) * te_v(k) + &
327                                           tsc(3) * te_vm(k) )
328
329          ENDDO
330          IF ( .NOT. constant_diffusion )  THEN
331             DO  k = nzb+1, nzt
332
333                e1d_p(k) = e1d(k) + dt_1d * ( tsc(2) * te_e(k) + &
334                                              tsc(3) * te_em(k) )
335
336             ENDDO
337!
338!--          Eliminate negative TKE values, which can result from the
339!--          integration due to numerical inaccuracies. In such cases the TKE
340!--          value is reduced to 10 percent of its old value.
341             WHERE ( e1d_p < 0.0 )  e1d_p = 0.1 * e1d
342          ENDIF
343
344!
345!--       Calculate tendencies for the next Runge-Kutta step
346          IF ( timestep_scheme(1:5) == 'runge' ) THEN
347             IF ( intermediate_timestep_count == 1 )  THEN
348
349                DO  k = nzb+1, nzt
350                   te_um(k) = te_u(k)
351                   te_vm(k) = te_v(k)
352                ENDDO
353
354                IF ( .NOT. constant_diffusion )  THEN
355                   DO k = nzb+1, nzt
356                      te_em(k) = te_e(k)
357                   ENDDO
358                ENDIF
359
360             ELSEIF ( intermediate_timestep_count < &
361                         intermediate_timestep_count_max )  THEN
362
363                DO  k = nzb+1, nzt
364                   te_um(k) = -9.5625 * te_u(k) + 5.3125 * te_um(k)
365                   te_vm(k) = -9.5625 * te_v(k) + 5.3125 * te_vm(k)
366                ENDDO
367
368                IF ( .NOT. constant_diffusion )  THEN
369                   DO k = nzb+1, nzt
370                      te_em(k) = -9.5625 * te_e(k) + 5.3125 * te_em(k)
371                   ENDDO
372                ENDIF
373
374             ENDIF
375          ENDIF
376
377
378!
379!--       Boundary conditions for the prognostic variables.
380!--       At the top boundary (nzt+1) u,v and e keep their initial values
381!--       (ug(nzt+1), vg(nzt+1), 0), at the bottom boundary the mirror
382!--       boundary condition applies to u and v.
383!--       The boundary condition for e is set further below ( (u*/cm)**2 ).
384         ! u1d_p(nzb) = -u1d_p(nzb+1)
385         ! v1d_p(nzb) = -v1d_p(nzb+1)
386
387          u1d_p(nzb) = 0.0
388          v1d_p(nzb) = 0.0
389
390!
391!--       Swap the time levels in preparation for the next time step.
392          u1d  = u1d_p
393          v1d  = v1d_p
394          IF ( .NOT. constant_diffusion )  THEN
395             e1d  = e1d_p
396          ENDIF
397
398!
399!--       Compute diffusion quantities
400          IF ( .NOT. constant_diffusion )  THEN
401
402!
403!--          First compute the vertical fluxes in the Prandtl-layer
404             IF ( prandtl_layer )  THEN
405!
406!--             Compute theta* using Rif numbers of the previous time step
407                IF ( rif1d(1) >= 0.0 )  THEN
408!
409!--                Stable stratification
410                   ts1d = kappa * ( pt_init(nzb+1) - pt_init(nzb) ) /       &
411                          ( LOG( zu(nzb+1) / z0h1d ) + 5.0 * rif1d(nzb+1) * &
412                                          ( zu(nzb+1) - z0h1d ) / zu(nzb+1) &
413                          )
414                ELSE
415!
416!--                Unstable stratification
417                   a = SQRT( 1.0 - 16.0 * rif1d(nzb+1) )
418                   b = SQRT( 1.0 - 16.0 * rif1d(nzb+1) / zu(nzb+1) * z0h1d )
419!
420!--                In the borderline case the formula for stable stratification
421!--                must be applied, because otherwise a zero division would
422!--                occur in the argument of the logarithm.
423                   IF ( a == 0.0  .OR.  b == 0.0 )  THEN
424                      ts1d = kappa * ( pt_init(nzb+1) - pt_init(nzb) ) /       &
425                             ( LOG( zu(nzb+1) / z0h1d ) + 5.0 * rif1d(nzb+1) * &
426                                             ( zu(nzb+1) - z0h1d ) / zu(nzb+1) &
427                             )
428                   ELSE
429                      ts1d = kappa * ( pt_init(nzb+1) - pt_init(nzb) ) / &
430                             LOG( (a-1.0) / (a+1.0) * (b+1.0) / (b-1.0) )
431                   ENDIF
432                ENDIF
433
434             ENDIF    ! prandtl_layer
435
436!
437!--          Compute the Richardson-flux numbers,
438!--          first at the top of the Prandtl-layer using u* of the previous
439!--          time step (+1E-30, if u* = 0), then in the remaining area. There
440!--          the rif-numbers of the previous time step are used.
441
442             IF ( prandtl_layer )  THEN
443                IF ( .NOT. humidity )  THEN
444                   pt_0 = pt_init(nzb+1)
445                   flux = ts1d
446                ELSE
447                   pt_0 = pt_init(nzb+1) * ( 1.0 + 0.61 * q_init(nzb+1) )
448                   flux = ts1d + 0.61 * pt_init(k) * qs1d
449                ENDIF
450                rif1d(nzb+1) = zu(nzb+1) * kappa * g * flux / &
451                               ( pt_0 * ( us1d**2 + 1E-30 ) )
452             ENDIF
453
454             DO  k = nzb_diff, nzt
455                IF ( .NOT. humidity )  THEN
456                   pt_0 = pt_init(k)
457                   flux = ( pt_init(k+1) - pt_init(k-1) ) * dd2zu(k)
458                ELSE
459                   pt_0 = pt_init(k) * ( 1.0 + 0.61 * q_init(k) )
460                   flux = ( ( pt_init(k+1) - pt_init(k-1) )                    &
461                            + 0.61 * pt_init(k) * ( q_init(k+1) - q_init(k-1) )&
462                          ) * dd2zu(k)
463                ENDIF
464                IF ( rif1d(k) >= 0.0 )  THEN
465                   rif1d(k) = g / pt_0 * flux /                              &
466                              (  ( ( u1d(k+1) - u1d(k-1) ) * dd2zu(k) )**2   &
467                               + ( ( v1d(k+1) - v1d(k-1) ) * dd2zu(k) )**2   &
468                               + 1E-30                                       &
469                              )
470                ELSE
471                   rif1d(k) = g / pt_0 * flux /                              &
472                              (  ( ( u1d(k+1) - u1d(k-1) ) * dd2zu(k) )**2   &
473                               + ( ( v1d(k+1) - v1d(k-1) ) * dd2zu(k) )**2   &
474                               + 1E-30                                       &
475                              ) * ( 1.0 - 16.0 * rif1d(k) )**0.25
476                ENDIF
477             ENDDO
478!
479!--          Richardson-numbers must remain restricted to a realistic value
480!--          range. It is exceeded excessively for very small velocities
481!--          (u,v --> 0).
482             WHERE ( rif1d < rif_min )  rif1d = rif_min
483             WHERE ( rif1d > rif_max )  rif1d = rif_max
484
485!
486!--          Compute u* from the absolute velocity value
487             IF ( prandtl_layer )  THEN
488                uv_total = SQRT( u1d(nzb+1)**2 + v1d(nzb+1)**2 )
489
490                IF ( rif1d(nzb+1) >= 0.0 )  THEN
491!
492!--                Stable stratification
493                   us1d = kappa * uv_total / (                                 &
494                             LOG( zu(nzb+1) / z01d ) + 5.0 * rif1d(nzb+1) *    &
495                                              ( zu(nzb+1) - z01d ) / zu(nzb+1) &
496                                             )
497                ELSE
498!
499!--                Unstable stratification
500                   a = 1.0 / SQRT( SQRT( 1.0 - 16.0 * rif1d(nzb+1) ) )
501                   b = 1.0 / SQRT( SQRT( 1.0 - 16.0 * rif1d(nzb+1) / zu(nzb+1) &
502                                                    * z01d ) )
503!
504!--                In the borderline case the formula for stable stratification
505!--                must be applied, because otherwise a zero division would
506!--                occur in the argument of the logarithm.
507                   IF ( a == 1.0  .OR.  b == 1.0 )  THEN
508                      us1d = kappa * uv_total / (                            &
509                             LOG( zu(nzb+1) / z01d ) +                       &
510                             5.0 * rif1d(nzb+1) * ( zu(nzb+1) - z01d ) /     &
511                                                  zu(nzb+1) )
512                   ELSE
513                      us1d = kappa * uv_total / (                              &
514                                 LOG( (1.0+b) / (1.0-b) * (1.0-a) / (1.0+a) ) +&
515                                 2.0 * ( ATAN( b ) - ATAN( a ) )               &
516                                                )
517                   ENDIF
518                ENDIF
519
520!
521!--             Compute the momentum fluxes for the diffusion terms
522                usws1d  = - u1d(nzb+1) / uv_total * us1d**2
523                vsws1d  = - v1d(nzb+1) / uv_total * us1d**2
524
525!
526!--             Boundary condition for the turbulent kinetic energy at the top
527!--             of the Prandtl-layer. c_m = 0.4 according to Detering.
528!--             Additional Neumann condition de/dz = 0 at nzb is set to ensure
529!--             compatibility with the 3D model.
530                IF ( ibc_e_b == 2 )  THEN
531                   e1d(nzb+1) = ( us1d / 0.1 )**2
532!                  e1d(nzb+1) = ( us1d / 0.4 )**2  !not used so far, see also
533                                                   !prandtl_fluxes
534                ENDIF
535                e1d(nzb) = e1d(nzb+1)
536
537                IF ( humidity .OR. passive_scalar ) THEN
538!
539!--                Compute q*
540                   IF ( rif1d(1) >= 0.0 )  THEN
541!
542!--                Stable stratification
543                   qs1d = kappa * ( q_init(nzb+1) - q_init(nzb) ) /         &
544                          ( LOG( zu(nzb+1) / z0h1d ) + 5.0 * rif1d(nzb+1) * &
545                                          ( zu(nzb+1) - z0h1d ) / zu(nzb+1) &
546                          )
547                ELSE
548!
549!--                Unstable stratification
550                   a = SQRT( 1.0 - 16.0 * rif1d(nzb+1) )
551                   b = SQRT( 1.0 - 16.0 * rif1d(nzb+1) / zu(nzb+1) * z0h1d )
552!
553!--                In the borderline case the formula for stable stratification
554!--                must be applied, because otherwise a zero division would
555!--                occur in the argument of the logarithm.
556                   IF ( a == 1.0  .OR.  b == 1.0 )  THEN
557                      qs1d = kappa * ( q_init(nzb+1) - q_init(nzb) ) /         &
558                             ( LOG( zu(nzb+1) / z0h1d ) + 5.0 * rif1d(nzb+1) * &
559                                             ( zu(nzb+1) - z0h1d ) / zu(nzb+1) &
560                             )
561                   ELSE
562                      qs1d = kappa * ( q_init(nzb+1) - q_init(nzb) ) / &
563                             LOG( (a-1.0) / (a+1.0) * (b+1.0) / (b-1.0) )
564                   ENDIF
565                ENDIF               
566                ELSE
567                   qs1d = 0.0
568                ENDIF             
569
570             ENDIF   !  prandtl_layer
571
572!
573!--          Compute the diabatic mixing length
574             IF ( mixing_length_1d == 'blackadar' )  THEN
575                DO  k = nzb+1, nzt
576                   IF ( rif1d(k) >= 0.0 )  THEN
577                      l1d(k) = l_black(k) / ( 1.0 + 5.0 * rif1d(k) )
578                   ELSE
579                      l1d(k) = l_black(k) * ( 1.0 - 16.0 * rif1d(k) )**0.25
580                   ENDIF
581                   l1d(k) = l_black(k)
582                ENDDO
583
584             ELSEIF ( mixing_length_1d == 'as_in_3d_model' )  THEN
585                DO  k = nzb+1, nzt
586                   dpt_dz = ( pt_init(k+1) - pt_init(k-1) ) * dd2zu(k)
587                   IF ( dpt_dz > 0.0 )  THEN
588                      l_stable = 0.76 * SQRT( e1d(k) ) / &
589                                     SQRT( g / pt_init(k) * dpt_dz ) + 1E-5
590                   ELSE
591                      l_stable = l_grid(k)
592                   ENDIF
593                   l1d(k) = MIN( l_grid(k), l_stable )
594                ENDDO
595             ENDIF
596
597!
598!--          Compute the diffusion coefficients for momentum via the
599!--          corresponding Prandtl-layer relationship and according to
600!--          Prandtl-Kolmogorov, respectively. The unstable stratification is
601!--          computed via the adiabatic mixing length, for the unstability has
602!--          already been taken account of via the TKE (cf. also Diss.).
603             IF ( prandtl_layer )  THEN
604                IF ( rif1d(nzb+1) >= 0.0 )  THEN
605                   km1d(nzb+1) = us1d * kappa * zu(nzb+1) / &
606                                 ( 1.0 + 5.0 * rif1d(nzb+1) )
607                ELSE
608                   km1d(nzb+1) = us1d * kappa * zu(nzb+1) * &
609                                 ( 1.0 - 16.0 * rif1d(nzb+1) )**0.25
610                ENDIF
611             ENDIF
612             DO  k = nzb_diff, nzt
613!                km1d(k) = 0.4 * SQRT( e1d(k) ) !changed: adjustment to 3D-model
614                km1d(k) = 0.1 * SQRT( e1d(k) )
615                IF ( rif1d(k) >= 0.0 )  THEN
616                   km1d(k) = km1d(k) * l1d(k)
617                ELSE
618                   km1d(k) = km1d(k) * l_black(k)
619                ENDIF
620             ENDDO
621
622!
623!--          Add damping layer
624             DO  k = damp_level_ind_1d+1, nzt+1
625                km1d(k) = 1.1 * km1d(k-1)
626                km1d(k) = MIN( km1d(k), 10.0 )
627             ENDDO
628
629!
630!--          Compute the diffusion coefficient for heat via the relationship
631!--          kh = phim / phih * km
632             DO  k = nzb+1, nzt
633                IF ( rif1d(k) >= 0.0 )  THEN
634                   kh1d(k) = km1d(k)
635                ELSE
636                   kh1d(k) = km1d(k) * ( 1.0 - 16.0 * rif1d(k) )**0.25
637                ENDIF
638             ENDDO
639
640          ENDIF   ! .NOT. constant_diffusion
641
642       ENDDO   ! intermediate step loop
643
644!
645!--    Increment simulated time and output times
646       current_timestep_number_1d = current_timestep_number_1d + 1
647       simulated_time_1d          = simulated_time_1d + dt_1d
648       simulated_time_chr         = time_to_string( simulated_time_1d )
649       time_pr_1d                 = time_pr_1d          + dt_1d
650       time_run_control_1d        = time_run_control_1d + dt_1d
651
652!
653!--    Determine and print out quantities for run control
654       IF ( time_run_control_1d >= dt_run_control_1d )  THEN
655          CALL run_control_1d
656          time_run_control_1d = time_run_control_1d - dt_run_control_1d
657       ENDIF
658
659!
660!--    Profile output on file
661       IF ( time_pr_1d >= dt_pr_1d )  THEN
662          CALL print_1d_model
663          time_pr_1d = time_pr_1d - dt_pr_1d
664       ENDIF
665
666!
667!--    Determine size of next time step
668       CALL timestep_1d
669
670    ENDDO   ! time loop
671
672
673 END SUBROUTINE time_integration_1d
674
675
676 SUBROUTINE run_control_1d
677
678!------------------------------------------------------------------------------!
679! Description:
680! ------------
681! Compute and print out quantities for run control of the 1D model.
682!------------------------------------------------------------------------------!
683
684    USE constants
685    USE indices
686    USE model_1d
687    USE pegrid
688    USE control_parameters
689
690    IMPLICIT NONE
691
692    INTEGER ::  k
693    REAL    ::  alpha, energy, umax, uv_total, vmax
694
695!
696!-- Output
697    IF ( myid == 0 )  THEN
698!
699!--    If necessary, write header
700       IF ( .NOT. run_control_header_1d )  THEN
701          CALL check_open( 15 )
702          WRITE ( 15, 100 )
703          run_control_header_1d = .TRUE.
704       ENDIF
705
706!
707!--    Compute control quantities
708!--    grid level nzp is excluded due to mirror boundary condition
709       umax = 0.0; vmax = 0.0; energy = 0.0
710       DO  k = nzb+1, nzt+1
711          umax = MAX( ABS( umax ), ABS( u1d(k) ) )
712          vmax = MAX( ABS( vmax ), ABS( v1d(k) ) )
713          energy = energy + 0.5 * ( u1d(k)**2 + v1d(k)**2 )
714       ENDDO
715       energy = energy / REAL( nzt - nzb + 1 )
716
717       uv_total = SQRT( u1d(nzb+1)**2 + v1d(nzb+1)**2 )
718       IF ( ABS( v1d(nzb+1) ) .LT. 1.0E-5 )  THEN
719          alpha = ACOS( SIGN( 1.0 , u1d(nzb+1) ) )
720       ELSE
721          alpha = ACOS( u1d(nzb+1) / uv_total )
722          IF ( v1d(nzb+1) <= 0.0 )  alpha = 2.0 * pi - alpha
723       ENDIF
724       alpha = alpha / ( 2.0 * pi ) * 360.0
725
726       WRITE ( 15, 101 )  current_timestep_number_1d, simulated_time_chr, &
727                          dt_1d, umax, vmax, us1d, alpha, energy
728!
729!--    Write buffer contents to disc immediately
730       CALL local_flush( 15 )
731
732    ENDIF
733
734!
735!-- formats
736100 FORMAT (///'1D-Zeitschrittkontrollausgaben:'/ &
737              &'------------------------------'// &
738           &'ITER.  HH:MM:SS    DT      UMAX   VMAX    U*   ALPHA   ENERG.'/ &
739           &'-------------------------------------------------------------')
740101 FORMAT (I5,2X,A9,1X,F6.2,2X,F6.2,1X,F6.2,2X,F5.3,2X,F5.1,2X,F7.2)
741
742
743 END SUBROUTINE run_control_1d
744
745
746
747 SUBROUTINE timestep_1d
748
749!------------------------------------------------------------------------------!
750! Description:
751! ------------
752! Compute the time step w.r.t. the diffusion criterion
753!------------------------------------------------------------------------------!
754
755    USE arrays_3d
756    USE indices
757    USE model_1d
758    USE pegrid
759    USE control_parameters
760
761    IMPLICIT NONE
762
763    INTEGER ::  k
764    REAL    ::  div, dt_diff, fac, value
765
766
767!
768!-- Compute the currently feasible time step according to the diffusion
769!-- criterion. At nzb+1 the half grid length is used.
770    fac = 0.35
771    dt_diff = dt_max_1d
772    DO  k = nzb+2, nzt
773       value   = fac * dzu(k) * dzu(k) / ( km1d(k) + 1E-20 )
774       dt_diff = MIN( value, dt_diff )
775    ENDDO
776    value   = fac * zu(nzb+1) * zu(nzb+1) / ( km1d(nzb+1) + 1E-20 )
777    dt_1d = MIN( value, dt_diff )
778
779!
780!-- Set flag when the time step becomes too small
781    IF ( dt_1d < ( 0.00001 * dt_max_1d ) )  THEN
782       stop_dt_1d = .TRUE.
783
784       WRITE( message_string, * ) 'timestep has exceeded the lower limit &', &
785                                  'dt_1d = ',dt_1d,' s   simulation stopped!'
786       CALL message( 'timestep_1d', 'PA0192', 1, 2, 0, 6, 0 )
787       
788    ENDIF
789
790!
791!-- A more or less simple new time step value is obtained taking only the
792!-- first two significant digits
793    div = 1000.0
794    DO  WHILE ( dt_1d < div )
795       div = div / 10.0
796    ENDDO
797    dt_1d = NINT( dt_1d * 100.0 / div ) * div / 100.0
798
799    old_dt_1d = dt_1d
800
801
802 END SUBROUTINE timestep_1d
803
804
805
806 SUBROUTINE print_1d_model
807
808!------------------------------------------------------------------------------!
809! Description:
810! ------------
811! List output of profiles from the 1D-model
812!------------------------------------------------------------------------------!
813
814    USE arrays_3d
815    USE indices
816    USE model_1d
817    USE pegrid
818    USE control_parameters
819
820    IMPLICIT NONE
821
822
823    INTEGER ::  k
824
825
826    IF ( myid == 0 )  THEN
827!
828!--    Open list output file for profiles from the 1D-model
829       CALL check_open( 17 )
830
831!
832!--    Write Header
833       WRITE ( 17, 100 )  TRIM( run_description_header ), &
834                          TRIM( simulated_time_chr )
835       WRITE ( 17, 101 )
836
837!
838!--    Write the values
839       WRITE ( 17, 102 )
840       WRITE ( 17, 101 )
841       DO  k = nzt+1, nzb, -1
842          WRITE ( 17, 103)  k, zu(k), u1d(k), v1d(k), pt_init(k), e1d(k), &
843                            rif1d(k), km1d(k), kh1d(k), l1d(k), zu(k), k
844       ENDDO
845       WRITE ( 17, 101 )
846       WRITE ( 17, 102 )
847       WRITE ( 17, 101 )
848
849!
850!--    Write buffer contents to disc immediately
851       CALL local_flush( 17 )
852
853    ENDIF
854
855!
856!-- Formats
857100 FORMAT (//1X,A/1X,10('-')/' 1d-model profiles'/ &
858            ' Time: ',A)
859101 FORMAT (1X,79('-'))
860102 FORMAT ('   k     zu      u      v     pt      e    rif    Km    Kh     ', &
861            'l      zu      k')
862103 FORMAT (1X,I4,1X,F7.1,1X,F6.2,1X,F6.2,1X,F6.2,1X,F6.2,1X,F5.2,1X,F5.2, &
863            1X,F5.2,1X,F6.2,1X,F7.1,2X,I4)
864
865
866 END SUBROUTINE print_1d_model
Note: See TracBrowser for help on using the repository browser.