source: palm/trunk/SOURCE/advec_u_pw.f90 @ 164

Last change on this file since 164 was 110, checked in by raasch, 16 years ago

New:
---
Allows runs for a coupled atmosphere-ocean LES,
coupling frequency is controlled by new d3par-parameter dt_coupling,
the coupling mode (atmosphere_to_ocean or ocean_to_atmosphere) for the
respective processes is read from environment variable coupling_mode,
which is set by the mpiexec-command,
communication between the two models is done using the intercommunicator
comm_inter,
local files opened by the ocean model get the additional suffic "_O".
Assume saturation at k=nzb_s_inner(j,i) for atmosphere coupled to ocean.

A momentum flux can be set as top boundary condition using the new
inipar parameter top_momentumflux_u|v.

Non-cyclic boundary conditions can be used along all horizontal directions.

Quantities w*p* and w"e can be output as vertical profiles.

Initial profiles are reset to constant profiles in case that initializing_actions /= 'set_constant_profiles'. (init_rankine)

Optionally calculate km and kh from initial TKE e_init.

Changed:


Remaining variables iran changed to iran_part (advec_particles, init_particles).

In case that the presure solver is not called for every Runge-Kutta substep
(call_psolver_at_all_substeps = .F.), it is called after the first substep
instead of the last. In that case, random perturbations are also added to the
velocity field after the first substep.

Initialization of km,kh = 0.00001 for ocean = .T. (for ocean = .F. it remains 0.01).

Allow data_output_pr= q, wq, w"q", w*q* for humidity = .T. (instead of cloud_physics = .T.).

Errors:


Bugs from code parts for non-cyclic boundary conditions are removed: loops for
u and v are starting from index nxlu, nysv, respectively. The radiation boundary
condition is used for every Runge-Kutta substep. Velocity phase speeds for
the radiation boundary conditions are calculated for the first Runge-Kutta
substep only and reused for the further substeps. New arrays c_u, c_v, and c_w
are defined for this purpose. Several index errors are removed from the
radiation boundary condition code parts. Upper bounds for calculating
u_0 and v_0 (in production_e) are nxr+1 and nyn+1 because otherwise these
values are not available in case of non-cyclic boundary conditions.

+dots_num_palm in module user, +module netcdf_control in user_init (both in user_interface)

Bugfix: wrong sign removed from the buoyancy production term in the case use_reference = .T. (production_e)

Bugfix: Error message concerning output of particle concentration (pc) modified (check_parameters).

Bugfix: Rayleigh damping for ocean fixed.

  • Property svn:keywords set to Id
File size: 3.6 KB
Line 
1 MODULE advec_u_pw_mod
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: advec_u_pw.f90 110 2007-10-05 05:13:14Z raasch $
11!
12! 106 2007-08-16 14:30:26Z raasch
13! i loop is starting from nxlu (needed for non-cyclic boundary conditions)
14!
15! 75 2007-03-22 09:54:05Z raasch
16! uxrp eliminated
17!
18! RCS Log replace by Id keyword, revision history cleaned up
19!
20! Revision 1.15  2006/02/23 09:44:21  raasch
21! nzb_2d replaced by nzb_u_inner
22!
23! Revision 1.1  1997/08/11 06:09:21  raasch
24! Initial revision
25!
26!
27! Description:
28! ------------
29! Advection term for u velocity-component using Piacsek and Williams.
30! Vertical advection at the first grid point above the surface is done with
31! normal centred differences, because otherwise no information from the surface
32! would be communicated upwards due to w=0 at K=nzb.
33!------------------------------------------------------------------------------!
34
35    PRIVATE
36    PUBLIC advec_u_pw
37
38    INTERFACE advec_u_pw
39       MODULE PROCEDURE advec_u_pw
40       MODULE PROCEDURE advec_u_pw_ij
41    END INTERFACE advec_u_pw
42 
43 CONTAINS
44
45
46!------------------------------------------------------------------------------!
47! Call for all grid points
48!------------------------------------------------------------------------------!
49    SUBROUTINE advec_u_pw
50
51       USE arrays_3d
52       USE control_parameters
53       USE grid_variables
54       USE indices
55
56       IMPLICIT NONE
57
58       INTEGER ::  i, j, k
59       REAL    ::  gu, gv
60 
61       gu = 2.0 * u_gtrans
62       gv = 2.0 * v_gtrans
63       DO  i = nxlu, nxr
64          DO  j = nys, nyn
65             DO  k = nzb_u_inner(j,i)+1, nzt
66                tend(k,j,i) = tend(k,j,i) - 0.25 * (                           &
67                         ( u(k,j,i+1) * ( u(k,j,i+1) + u(k,j,i) - gu )         &
68                         - u(k,j,i-1) * ( u(k,j,i) + u(k,j,i-1) - gu ) ) * ddx &
69                       + ( u(k,j+1,i) * ( v(k,j+1,i) + v(k,j+1,i-1) - gv )     &
70                         - u(k,j-1,i) * ( v(k,j,i) + v(k,j,i-1) - gv ) ) * ddy &
71                       + ( u(k+1,j,i) * ( w(k,j,i) + w(k,j,i-1) )              &
72                         - u(k-1,j,i) * ( w(k-1,j,i) + w(k-1,j,i-1) ) )        &
73                                                                  * ddzw(k)    &
74                                                   )
75             ENDDO
76          ENDDO
77       ENDDO
78
79    END SUBROUTINE advec_u_pw
80
81
82!------------------------------------------------------------------------------!
83! Call for grid point i,j
84!------------------------------------------------------------------------------!
85    SUBROUTINE advec_u_pw_ij( i, j )
86
87       USE arrays_3d
88       USE control_parameters
89       USE grid_variables
90       USE indices
91
92       IMPLICIT NONE
93
94       INTEGER ::  i, j, k
95       REAL    ::  gu, gv
96
97       gu = 2.0 * u_gtrans
98       gv = 2.0 * v_gtrans
99       DO  k = nzb_u_inner(j,i)+1, nzt
100          tend(k,j,i) = tend(k,j,i) - 0.25 * (                                 &
101                         ( u(k,j,i+1) * ( u(k,j,i+1) + u(k,j,i) - gu )         &
102                         - u(k,j,i-1) * ( u(k,j,i) + u(k,j,i-1) - gu ) ) * ddx &
103                       + ( u(k,j+1,i) * ( v(k,j+1,i) + v(k,j+1,i-1) - gv )     &
104                         - u(k,j-1,i) * ( v(k,j,i) + v(k,j,i-1) - gv ) ) * ddy &
105                       + ( u(k+1,j,i) * ( w(k,j,i) + w(k,j,i-1) )              &
106                         - u(k-1,j,i) * ( w(k-1,j,i) + w(k-1,j,i-1) ) )        &
107                                                                  * ddzw(k)    &
108                                             )
109       ENDDO
110
111    END SUBROUTINE advec_u_pw_ij
112
113 END MODULE advec_u_pw_mod
Note: See TracBrowser for help on using the repository browser.