source: palm/trunk/SOURCE/exchange_horiz_2d.f90 @ 220

Last change on this file since 220 was 77, checked in by raasch, 17 years ago

New:
---

particle reflection from vertical walls implemented, particle SGS model adjusted to walls

Wall functions for vertical walls now include diabatic conditions. New subroutines wall_fluxes, wall_fluxes_e. New 4D-array rif_wall.

new d3par-parameter netcdf_64bit_3d to switch on 64bit offset only for 3D files

new d3par-parameter dt_max to define the maximum value for the allowed timestep

new inipar-parameter loop_optimization to control the loop optimization method

new inipar-parameter pt_refrence. If given, this value is used as the reference that in buoyancy terms (otherwise, the instantaneous horizontally averaged temperature is used).

new user interface user_advec_particles

new initializing action "by_user" calls user_init_3d_model and allows the initial setting of all 3d arrays

topography height informations are stored on arrays zu_s_inner and zw_w_inner and output to the 2d/3d NetCDF files

samples added to the user interface which show how to add user-define time series quantities.

calculation/output of precipitation amount, precipitation rate and z0 (by setting "pra*", "prr*", "z0*" with data_output). The time interval on which the precipitation amount is defined is set by new d3par-parameter precipitation_amount_interval

unit 9 opened for debug output (file DEBUG_<pe#>)

Makefile, advec_particles, average_3d_data, buoyancy, calc_precipitation, check_open, check_parameters, data_output_2d, diffusion_e, diffusion_u, diffusion_v, diffusion_w, diffusivities, header, impact_of_latent_heat, init_particles, init_3d_model, modules, netcdf, parin, production_e, read_var_list, read_3d_binary, sum_up_3d_data, user_interface, write_var_list, write_3d_binary

New: wall_fluxes

Changed:


General revision of non-cyclic horizontal boundary conditions: radiation boundary conditions are now used instead of Neumann conditions at the outflow (calculation needs velocity values for t-dt, which are stored on new arrays u_m_l, u_m_r, etc.), calculation of mean outflow is not needed any more, volume flow control is added for the outflow boundary (currently only for the north boundary!!), additional gridpoints along x and y (uxrp, vynp) are not needed any more, routine "boundary_conds" now operates on timelevel t+dt and is not split in two parts (main, uvw_outflow) any more, Neumann boundary conditions at inflow/outflow in case of non-cyclic boundary conditions for all 2d-arrays that are handled by exchange_horiz_2d

The FFT-method for solving the Poisson-equation is now working with Neumann boundary conditions both at the bottom and the top. This requires adjustments of the tridiagonal coefficients and subtracting the horizontally averaged mean from the vertical velocity field.

+age_m in particle_type

Particles-package is now part of the default code ("-p particles" is not needed any more).

Move call of user_actions( 'after_integration' ) below increment of times
and counters. user_actions is now called for each statistic region and has as an argument the number of the respective region (sr)

d3par-parameter data_output_ts removed. Timeseries output for "profil" removed. Timeseries are now switched on by dt_dots. Timeseries data is collected in flow_statistics.

Initial velocities at nzb+1 are regarded for volume flow control in case they have been set zero before (to avoid small timesteps); see new internal parameters u/v_nzb_p1_for_vfc.

q is not allowed to become negative (prognostic_equations).

poisfft_init is only called if fft-solver is switched on (init_pegrid).

d3par-parameter moisture renamed to humidity.

Subversion global revision number is read from mrun and added to the run description header and to the run control (_rc) file.

vtk directives removed from main program.

The uitility routine interpret_config reads PALM environment variables from NAMELIST instead using the system call GETENV.

advec_u_pw, advec_u_up, advec_v_pw, advec_v_up, asselin_filter, check_parameters, coriolis, data_output_dvrp, data_output_ptseries, data_output_ts, data_output_2d, data_output_3d, diffusion_u, diffusion_v, exchange_horiz, exchange_horiz_2d, flow_statistics, header, init_grid, init_particles, init_pegrid, init_rankine, init_pt_anomaly, init_1d_model, init_3d_model, modules, palm, package_parin, parin, poisfft, poismg, prandtl_fluxes, pres, production_e, prognostic_equations, read_var_list, read_3d_binary, sor, swap_timelevel, time_integration, write_var_list, write_3d_binary

Errors:


Bugfix: preset of tendencies te_em, te_um, te_vm in init_1d_model

Bugfix in sample for reading user defined data from restart file (user_init)

Bugfix in setting diffusivities for cases with the outflow damping layer extending over more than one subdomain (init_3d_model)

Check for possible negative humidities in the initial humidity profile.

in Makefile, default suffixes removed from the suffix list to avoid calling of m2c in
# case of .mod files

Makefile
check_parameters, init_1d_model, init_3d_model, user_interface

  • Property svn:keywords set to Id
File size: 5.7 KB
Line 
1 SUBROUTINE exchange_horiz_2d( ar )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: exchange_horiz_2d.f90 77 2007-03-29 04:26:56Z raasch $
11!
12! 73 2007-03-20 08:33:14Z raasch
13! Neumann boundary conditions at inflow/outflow in case of non-cyclic boundary
14! conditions
15!
16! RCS Log replace by Id keyword, revision history cleaned up
17!
18! Revision 1.9  2006/05/12 19:15:52  letzel
19! MPI_REAL replaced by MPI_INTEGER in exchange_horiz_2d_int
20!
21! Revision 1.1  1998/01/23 09:58:21  raasch
22! Initial revision
23!
24!
25! Description:
26! ------------
27! Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
28! boundary conditions, respectively, for 2D-arrays.
29!------------------------------------------------------------------------------!
30
31    USE control_parameters
32    USE cpulog
33    USE indices
34    USE interfaces
35    USE pegrid
36
37    IMPLICIT NONE
38
39    REAL ::  ar(nys-1:nyn+1,nxl-1:nxr+1)
40
41
42    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
43
44#if defined( __parallel )
45
46!
47!-- Exchange of lateral boundary values for parallel computers
48    IF ( pdims(1) == 1 )  THEN
49
50!
51!--    One-dimensional decomposition along y, boundary values can be exchanged
52!--    within the PE memory
53       ar(nys:nyn,nxl-1) = ar(nys:nyn,nxr)
54       ar(nys:nyn,nxr+1) = ar(nys:nyn,nxl)
55
56    ELSE
57!
58!--    Send left boundary, receive right one
59       CALL MPI_SENDRECV( ar(nys,nxl),   ngp_y, MPI_REAL, pleft,  0, &
60                          ar(nys,nxr+1), ngp_y, MPI_REAL, pright, 0, &
61                          comm2d, status, ierr )
62!
63!--    Send right boundary, receive left one
64       CALL MPI_SENDRECV( ar(nys,nxr),   ngp_y, MPI_REAL, pright,  1, &
65                          ar(nys,nxl-1), ngp_y, MPI_REAL, pleft,   1, &
66                          comm2d, status, ierr )
67    ENDIF
68
69    IF ( pdims(2) == 1 )  THEN
70!
71!--    One-dimensional decomposition along x, boundary values can be exchanged
72!--    within the PE memory
73       ar(nys-1,:) = ar(nyn,:)
74       ar(nyn+1,:) = ar(nys,:)
75
76    ELSE
77!
78!--    Send front boundary, receive rear one
79       CALL MPI_SENDRECV( ar(nys,nxl-1),   1, type_x, psouth, 0, &
80                          ar(nyn+1,nxl-1), 1, type_x, pnorth, 0, &
81                          comm2d, status, ierr )
82!
83!--    Send rear boundary, receive front one
84       CALL MPI_SENDRECV( ar(nyn,nxl-1),   1, type_x, pnorth, 1, &
85                          ar(nys-1,nxl-1), 1, type_x, psouth, 1, &
86                          comm2d, status, ierr )
87    ENDIF
88
89#else
90
91!
92!-- Lateral boundary conditions in the non-parallel case
93    IF ( bc_lr == 'cyclic' )  THEN
94       ar(nys:nyn,nxl-1) = ar(nys:nyn,nxr)
95       ar(nys:nyn,nxr+1) = ar(nys:nyn,nxl)
96    ENDIF
97
98    IF ( bc_ns == 'cyclic' )  THEN
99       ar(nys-1,:) = ar(nyn,:)
100       ar(nyn+1,:) = ar(nys,:)
101    ENDIF
102
103#endif
104
105!
106!-- Neumann-conditions at inflow/outflow in case of non-cyclic boundary
107!-- conditions
108    IF ( inflow_l .OR. outflow_l )  ar(:,nxl-1) = ar(:,nxl)
109    IF ( inflow_r .OR. outflow_r )  ar(:,nxr+1) = ar(:,nxr)
110    IF ( inflow_s .OR. outflow_s )  ar(nys-1,:) = ar(nys,:)
111    IF ( inflow_n .OR. outflow_n )  ar(nyn+1,:) = ar(nyn,:)
112
113    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
114
115 END SUBROUTINE exchange_horiz_2d
116
117
118
119 SUBROUTINE exchange_horiz_2d_int( ar )
120
121!------------------------------------------------------------------------------!
122! Description:
123! ------------
124! Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
125! boundary conditions, respectively, for 2D integer arrays.
126!------------------------------------------------------------------------------!
127
128    USE control_parameters
129    USE cpulog
130    USE indices
131    USE interfaces
132    USE pegrid
133
134    IMPLICIT NONE
135
136    INTEGER ::  ar(nys-1:nyn+1,nxl-1:nxr+1)
137
138
139    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
140
141#if defined( __parallel )
142
143!
144!-- Exchange of lateral boundary values for parallel computers
145    IF ( pdims(1) == 1 )  THEN
146
147!
148!--    One-dimensional decomposition along y, boundary values can be exchanged
149!--    within the PE memory
150       ar(nys:nyn,nxl-1) = ar(nys:nyn,nxr)
151       ar(nys:nyn,nxr+1) = ar(nys:nyn,nxl)
152
153    ELSE
154!
155!--    Send left boundary, receive right one
156       CALL MPI_SENDRECV( ar(nys,nxl),   ngp_y, MPI_INTEGER, pleft,  0, &
157                          ar(nys,nxr+1), ngp_y, MPI_INTEGER, pright, 0, &
158                          comm2d, status, ierr )
159!
160!--    Send right boundary, receive left one
161       CALL MPI_SENDRECV( ar(nys,nxr),   ngp_y, MPI_INTEGER, pright,  1, &
162                          ar(nys,nxl-1), ngp_y, MPI_INTEGER, pleft,   1, &
163                          comm2d, status, ierr )
164    ENDIF
165
166    IF ( pdims(2) == 1 )  THEN
167!
168!--    One-dimensional decomposition along x, boundary values can be exchanged
169!--    within the PE memory
170       ar(nys-1,:) = ar(nyn,:)
171       ar(nyn+1,:) = ar(nys,:)
172
173    ELSE
174!
175!--    Send front boundary, receive rear one
176       CALL MPI_SENDRECV( ar(nys,nxl-1),   1, type_x_int, psouth, 0, &
177                          ar(nyn+1,nxl-1), 1, type_x_int, pnorth, 0, &
178                          comm2d, status, ierr )
179!
180!--    Send rear boundary, receive front one
181       CALL MPI_SENDRECV( ar(nyn,nxl-1),   1, type_x_int, pnorth, 1, &
182                          ar(nys-1,nxl-1), 1, type_x_int, psouth, 1, &
183                          comm2d, status, ierr )
184    ENDIF
185
186#else
187
188!
189!-- Lateral boundary conditions in the non-parallel case
190    IF ( bc_lr == 'cyclic' )  THEN
191       ar(nys:nyn,nxl-1) = ar(nys:nyn,nxr)
192       ar(nys:nyn,nxr+1) = ar(nys:nyn,nxl)
193    ENDIF
194
195    IF ( bc_ns == 'cyclic' )  THEN
196       ar(nys-1,:) = ar(nyn,:)
197       ar(nyn+1,:) = ar(nys,:)
198    ENDIF
199
200#endif
201
202    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
203
204 END SUBROUTINE exchange_horiz_2d_int
Note: See TracBrowser for help on using the repository browser.