source: palm/tags/release-3.4/SOURCE/write_var_list.f90 @ 366

Last change on this file since 366 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: 15.8 KB
Line 
1 SUBROUTINE write_var_list
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: write_var_list.f90 110 2007-10-05 05:13:14Z raasch $
11!
12! 102 2007-07-27 09:09:17Z raasch
13! +top_momentumflux_u|v, time_coupling
14!
15! 95 2007-06-02 16:48:38Z raasch
16! +bc_sa_t, ocean, sa_init, sa_surface, sa_vertical_gradient,
17! sa_vertical_gradient_level, bottom/top_salinity_flux
18!
19! 87 2007-05-22 15:46:47Z raasch
20! +max_pr_user (version 3.1)
21!
22! 75 2007-03-22 09:54:05Z raasch
23! +loop_optimization, pt_refrence, moisture renamed humidity
24!
25! 20 2007-02-26 00:12:32Z raasch
26! +top_heatflux, use_top_fluxes
27!
28! RCS Log replace by Id keyword, revision history cleaned up
29!
30! Revision 1.34  2006/08/22 14:30:52  raasch
31! +dz_max
32!
33! Revision 1.1  1998/03/18 20:20:38  raasch
34! Initial revision
35!
36!
37! Description:
38! ------------
39! Writing values of control variables to restart-file (binary format)
40!------------------------------------------------------------------------------!
41
42    USE arrays_3d
43    USE averaging
44    USE control_parameters
45    USE grid_variables
46    USE indices
47    USE model_1d
48    USE pegrid
49    USE profil_parameter
50    USE statistics
51
52    IMPLICIT NONE
53
54    CHARACTER (LEN=10) ::  binary_version
55
56
57
58    binary_version = '3.1'
59
60    WRITE ( 14 )  binary_version    ! opened in write_3d_binary
61
62    WRITE ( 14 )  'nz                            '
63    WRITE ( 14 )  nz
64    WRITE ( 14 )  'max_pr_user                   '
65    WRITE ( 14 )  max_pr_user
66    WRITE ( 14 )  'statistic_regions             '
67    WRITE ( 14 )  statistic_regions
68
69!
70!-- Caution: After changes in the following parameter-list, the
71!-- -------  version number stored in the variable binary_version has to be
72!--          increased. The same changes must also be done in the parameter-
73!--          list in read_var_list.
74
75    WRITE ( 14 )  'adjust_mixing_length          '
76    WRITE ( 14 )  adjust_mixing_length
77    WRITE ( 14 )  'advected_distance_x           '
78    WRITE ( 14 )  advected_distance_x
79    WRITE ( 14 )  'advected_distance_y           '
80    WRITE ( 14 )  advected_distance_y
81    WRITE ( 14 )  'alpha_surface                 '
82    WRITE ( 14 )  alpha_surface
83    WRITE ( 14 )  'average_count_pr              '
84    WRITE ( 14 )  average_count_pr
85    WRITE ( 14 )  'average_count_sp              '
86    WRITE ( 14 )  average_count_sp
87    WRITE ( 14 )  'average_count_3d              '
88    WRITE ( 14 )  average_count_3d
89    WRITE ( 14 )  'bc_e_b                        '
90    WRITE ( 14 )  bc_e_b
91    WRITE ( 14 )  'bc_lr                         '
92    WRITE ( 14 )  bc_lr
93    WRITE ( 14 )  'bc_ns                         '
94    WRITE ( 14 )  bc_ns
95    WRITE ( 14 )  'bc_p_b                        '
96    WRITE ( 14 )  bc_p_b
97    WRITE ( 14 )  'bc_p_t                        '
98    WRITE ( 14 )  bc_p_t
99    WRITE ( 14 )  'bc_pt_b                       '
100    WRITE ( 14 )  bc_pt_b
101    WRITE ( 14 )  'bc_pt_t                       '
102    WRITE ( 14 )  bc_pt_t
103    WRITE ( 14 )  'bc_pt_t_val                   '
104    WRITE ( 14 )  bc_pt_t_val
105    WRITE ( 14 )  'bc_q_b                        '
106    WRITE ( 14 )  bc_q_b
107    WRITE ( 14 )  'bc_q_t                        '
108    WRITE ( 14 )  bc_q_t
109    WRITE ( 14 )  'bc_q_t_val                    '
110    WRITE ( 14 )  bc_q_t_val
111    WRITE ( 14 )  'bc_s_b                        '
112    WRITE ( 14 )  bc_s_b
113    WRITE ( 14 )  'bc_s_t                        '
114    WRITE ( 14 )  bc_s_t
115    WRITE ( 14 )  'bc_sa_t                       '
116    WRITE ( 14 )  bc_sa_t
117    WRITE ( 14 )  'bc_uv_b                       '
118    WRITE ( 14 )  bc_uv_b
119    WRITE ( 14 )  'bc_uv_t                       '
120    WRITE ( 14 )  bc_uv_t
121    WRITE ( 14 )  'bottom_salinityflux           '
122    WRITE ( 14 )  bottom_salinityflux
123    WRITE ( 14 )  'building_height               '
124    WRITE ( 14 )  building_height
125    WRITE ( 14 )  'building_length_x             '
126    WRITE ( 14 )  building_length_x
127    WRITE ( 14 )  'building_length_y             '
128    WRITE ( 14 )  building_length_y
129    WRITE ( 14 )  'building_wall_left            '
130    WRITE ( 14 )  building_wall_left
131    WRITE ( 14 )  'building_wall_south           '
132    WRITE ( 14 )  building_wall_south
133    WRITE ( 14 )  'cloud_droplets                '
134    WRITE ( 14 )  cloud_droplets
135    WRITE ( 14 )  'cloud_physics                 '
136    WRITE ( 14 )  cloud_physics
137    WRITE ( 14 )  'conserve_volume_flow          '
138    WRITE ( 14 )  conserve_volume_flow
139    WRITE ( 14 )  'current_timestep_number       '
140    WRITE ( 14 )  current_timestep_number
141    WRITE ( 14 )  'cut_spline_overshoot          '
142    WRITE ( 14 )  cut_spline_overshoot
143    WRITE ( 14 )  'damp_level_1d                 '
144    WRITE ( 14 )  damp_level_1d
145    WRITE ( 14 )  'dissipation_1d                '
146    WRITE ( 14 )  dissipation_1d
147    WRITE ( 14 )  'dt_fixed                      '
148    WRITE ( 14 )  dt_fixed
149    WRITE ( 14 )  'dt_pr_1d                      '
150    WRITE ( 14 )  dt_pr_1d
151    WRITE ( 14 )  'dt_run_control_1d             '
152    WRITE ( 14 )  dt_run_control_1d
153    WRITE ( 14 )  'dt_3d                         '
154    WRITE ( 14 )  dt_3d
155    WRITE ( 14 )  'dvrp_filecount                '
156    WRITE ( 14 )  dvrp_filecount
157    WRITE ( 14 )  'dx                            '
158    WRITE ( 14 )  dx
159    WRITE ( 14 )  'dy                            '
160    WRITE ( 14 )  dy
161    WRITE ( 14 )  'dz                            '
162    WRITE ( 14 )  dz
163    WRITE ( 14 )  'dz_max                        '
164    WRITE ( 14 )  dz_max
165    WRITE ( 14 )  'dz_stretch_factor             '
166    WRITE ( 14 )  dz_stretch_factor
167    WRITE ( 14 )  'dz_stretch_level              '
168    WRITE ( 14 )  dz_stretch_level
169    WRITE ( 14 )  'e_min                         '
170    WRITE ( 14 )  e_min
171    WRITE ( 14 )  'end_time_1d                   '
172    WRITE ( 14 )  end_time_1d
173    WRITE ( 14 )  'fft_method                    '
174    WRITE ( 14 )  fft_method
175    WRITE ( 14 )  'first_call_advec_particles    '
176    WRITE ( 14 )  first_call_advec_particles
177    WRITE ( 14 )  'galilei_transformation        '
178    WRITE ( 14 )  galilei_transformation
179    WRITE ( 14 )  'grid_matching                 '
180    WRITE ( 14 )  grid_matching
181    WRITE ( 14 )  'hom                           '
182    WRITE ( 14 )  hom
183    WRITE ( 14 )  'inflow_disturbance_begin      '
184    WRITE ( 14 )  inflow_disturbance_begin
185    WRITE ( 14 )  'inflow_disturbance_end        '
186    WRITE ( 14 )  inflow_disturbance_end
187    WRITE ( 14 )  'km_constant                   '
188    WRITE ( 14 )  km_constant
189    WRITE ( 14 )  'km_damp_max                   '
190    WRITE ( 14 )  km_damp_max
191    WRITE ( 14 )  'last_dt_change                '
192    WRITE ( 14 )  last_dt_change
193    WRITE ( 14 )  'long_filter_factor            '
194    WRITE ( 14 )  long_filter_factor
195    WRITE ( 14 )  'loop_optimization             '
196    WRITE ( 14 )  loop_optimization
197    WRITE ( 14 )  'mixing_length_1d              '
198    WRITE ( 14 )  mixing_length_1d
199    WRITE ( 14 )  'humidity                      '
200    WRITE ( 14 )  humidity
201    WRITE ( 14 )  'momentum_advec                '
202    WRITE ( 14 )  momentum_advec
203    WRITE ( 14 )  'netcdf_precision              '
204    WRITE ( 14 )  netcdf_precision
205    WRITE ( 14 )  'npex                          '
206    WRITE ( 14 )  npex
207    WRITE ( 14 )  'npey                          '
208    WRITE ( 14 )  npey
209    WRITE ( 14 )  'nsor_ini                      '
210    WRITE ( 14 )  nsor_ini
211    WRITE ( 14 )  'nx                            '
212    WRITE ( 14 )  nx
213    WRITE ( 14 )  'ny                            '
214    WRITE ( 14 )  ny
215    WRITE ( 14 )  'ocean                         '
216    WRITE ( 14 )  ocean
217    WRITE ( 14 )  'old_dt                        '
218    WRITE ( 14 )  old_dt
219    WRITE ( 14 )  'omega                         '
220    WRITE ( 14 )  omega
221    WRITE ( 14 )  'outflow_damping_width         '
222    WRITE ( 14 )  outflow_damping_width
223    WRITE ( 14 )  'overshoot_limit_e             '
224    WRITE ( 14 )  overshoot_limit_e
225    WRITE ( 14 )  'overshoot_limit_pt            '
226    WRITE ( 14 )  overshoot_limit_pt
227    WRITE ( 14 )  'overshoot_limit_u             '
228    WRITE ( 14 )  overshoot_limit_u
229    WRITE ( 14 )  'overshoot_limit_v             '
230    WRITE ( 14 )  overshoot_limit_v
231    WRITE ( 14 )  'overshoot_limit_w             '
232    WRITE ( 14 )  overshoot_limit_w
233    WRITE ( 14 )  'passive_scalar                '
234    WRITE ( 14 )  passive_scalar
235    WRITE ( 14 )  'phi                           '
236    WRITE ( 14 )  phi
237    WRITE ( 14 )  'prandtl_layer                 '
238    WRITE ( 14 )  prandtl_layer
239    WRITE ( 14 )  'precipitation                 '
240    WRITE ( 14 )  precipitation
241    WRITE ( 14 )  'pt_init                       '
242    WRITE ( 14 )  pt_init
243    WRITE ( 14 )  'pt_reference                  '
244    WRITE ( 14 )  pt_reference
245    WRITE ( 14 )  'pt_surface                    '
246    WRITE ( 14 )  pt_surface
247    WRITE ( 14 )  'pt_surface_initial_change     '
248    WRITE ( 14 )  pt_surface_initial_change
249    WRITE ( 14 )  'pt_vertical_gradient          '
250    WRITE ( 14 )  pt_vertical_gradient
251    WRITE ( 14 )  'pt_vertical_gradient_level    '
252    WRITE ( 14 )  pt_vertical_gradient_level
253    WRITE ( 14 )  'pt_vertical_gradient_level_ind'
254    WRITE ( 14 )  pt_vertical_gradient_level_ind
255    WRITE ( 14 )  'q_init                        '
256    WRITE ( 14 )  q_init
257    WRITE ( 14 )  'q_surface                     '
258    WRITE ( 14 )  q_surface
259    WRITE ( 14 )  'q_surface_initial_change      '
260    WRITE ( 14 )  q_surface_initial_change
261    WRITE ( 14 )  'q_vertical_gradient           '
262    WRITE ( 14 )  q_vertical_gradient
263    WRITE ( 14 )  'q_vertical_gradient_level     '
264    WRITE ( 14 )  q_vertical_gradient_level
265    WRITE ( 14 )  'q_vertical_gradient_level_ind '
266    WRITE ( 14 )  q_vertical_gradient_level_ind
267    WRITE ( 14 )  'radiation                     '
268    WRITE ( 14 )  radiation
269    WRITE ( 14 )  'random_generator              '
270    WRITE ( 14 )  random_generator
271    WRITE ( 14 )  'random_heatflux               '
272    WRITE ( 14 )  random_heatflux
273    WRITE ( 14 )  'rif_max                       '
274    WRITE ( 14 )  rif_max
275    WRITE ( 14 )  'rif_min                       '
276    WRITE ( 14 )  rif_min
277    WRITE ( 14 )  'roughness_length              '
278    WRITE ( 14 )  roughness_length
279    WRITE ( 14 )  'runnr                         '
280    WRITE ( 14 )  runnr
281    WRITE ( 14 )  'sa_init                       '
282    WRITE ( 14 )  sa_init
283    WRITE ( 14 )  'sa_surface                    '
284    WRITE ( 14 )  sa_surface
285    WRITE ( 14 )  'sa_vertical_gradient          '
286    WRITE ( 14 )  sa_vertical_gradient
287    WRITE ( 14 )  'sa_vertical_gradient_level    '
288    WRITE ( 14 )  sa_vertical_gradient_level
289    WRITE ( 14 )  'scalar_advec                  '
290    WRITE ( 14 )  scalar_advec
291    WRITE ( 14 )  'simulated_time                '
292    WRITE ( 14 )  simulated_time
293    WRITE ( 14 )  'surface_heatflux              '
294    WRITE ( 14 )  surface_heatflux
295    WRITE ( 14 )  'surface_pressure              '
296    WRITE ( 14 )  surface_pressure
297    WRITE ( 14 )  'surface_scalarflux            '
298    WRITE ( 14 )  surface_scalarflux   
299    WRITE ( 14 )  'surface_waterflux             '
300    WRITE ( 14 )  surface_waterflux   
301    WRITE ( 14 )  's_surface                     '
302    WRITE ( 14 )  s_surface
303    WRITE ( 14 )  's_surface_initial_change      '
304    WRITE ( 14 )  s_surface_initial_change
305    WRITE ( 14 )  's_vertical_gradient           '
306    WRITE ( 14 )  s_vertical_gradient
307    WRITE ( 14 )  's_vertical_gradient_level     '
308    WRITE ( 14 )  s_vertical_gradient_level
309    WRITE ( 14 )  'time_coupling                 '
310    WRITE ( 14 )  time_coupling
311    WRITE ( 14 )  'time_disturb                  '
312    WRITE ( 14 )  time_disturb
313    WRITE ( 14 )  'time_dopr                     '
314    WRITE ( 14 )  time_dopr
315    WRITE ( 14 )  'time_dopr_av                  '
316    WRITE ( 14 )  time_dopr_av
317    WRITE ( 14 )  'time_dopr_listing             '
318    WRITE ( 14 )  time_dopr_listing
319    WRITE ( 14 )  'time_dopts                    '
320    WRITE ( 14 )  time_dopts
321    WRITE ( 14 )  'time_dosp                     '
322    WRITE ( 14 )  time_dosp
323    WRITE ( 14 )  'time_dots                     '
324    WRITE ( 14 )  time_dots
325    WRITE ( 14 )  'time_do2d_xy                  '
326    WRITE ( 14 )  time_do2d_xy
327    WRITE ( 14 )  'time_do2d_xz                  '
328    WRITE ( 14 )  time_do2d_xz
329    WRITE ( 14 )  'time_do2d_yz                  '
330    WRITE ( 14 )  time_do2d_yz
331    WRITE ( 14 )  'time_do3d                     '
332    WRITE ( 14 )  time_do3d
333    WRITE ( 14 )  'time_do_av                    '
334    WRITE ( 14 )  time_do_av
335    WRITE ( 14 )  'time_do_sla                   '
336    WRITE ( 14 )  time_do_sla
337    WRITE ( 14 )  'time_dvrp                     '
338    WRITE ( 14 )  time_dvrp
339    WRITE ( 14 )  'time_restart                  '
340    WRITE ( 14 )  time_restart
341    WRITE ( 14 )  'time_run_control              '
342    WRITE ( 14 )  time_run_control
343    WRITE ( 14 )  'timestep_scheme               '
344    WRITE ( 14 )  timestep_scheme
345    WRITE ( 14 )  'topography                    '
346    WRITE ( 14 )  topography
347    WRITE ( 14 )  'top_heatflux                  '
348    WRITE ( 14 )  top_heatflux
349    WRITE ( 14 )  'top_momentumflux_u            '
350    WRITE ( 14 )  top_momentumflux_u
351    WRITE ( 14 )  'top_momentumflux_v            '
352    WRITE ( 14 )  top_momentumflux_v
353    WRITE ( 14 )  'top_salinityflux              '
354    WRITE ( 14 )  top_salinityflux
355    WRITE ( 14 )  'tsc                           '
356    WRITE ( 14 )  tsc
357    WRITE ( 14 )  'u_init                        '
358    WRITE ( 14 )  u_init
359    WRITE ( 14 )  'u_max                         '
360    WRITE ( 14 )  u_max
361    WRITE ( 14 )  'u_max_ijk                     '
362    WRITE ( 14 )  u_max_ijk
363    WRITE ( 14 )  'ug                            '
364    WRITE ( 14 )  ug
365    WRITE ( 14 )  'ug_surface                    '
366    WRITE ( 14 )  ug_surface
367    WRITE ( 14 )  'ug_vertical_gradient          '
368    WRITE ( 14 )  ug_vertical_gradient
369    WRITE ( 14 )  'ug_vertical_gradient_level    '
370    WRITE ( 14 )  ug_vertical_gradient_level
371    WRITE ( 14 )  'ug_vertical_gradient_level_ind'
372    WRITE ( 14 )  ug_vertical_gradient_level_ind
373    WRITE ( 14 )  'ups_limit_e                   '
374    WRITE ( 14 )  ups_limit_e
375    WRITE ( 14 )  'ups_limit_pt                  '
376    WRITE ( 14 )  ups_limit_pt
377    WRITE ( 14 )  'ups_limit_u                   '
378    WRITE ( 14 )  ups_limit_u
379    WRITE ( 14 )  'ups_limit_v                   '
380    WRITE ( 14 )  ups_limit_v
381    WRITE ( 14 )  'ups_limit_w                   '
382    WRITE ( 14 )  ups_limit_w
383    WRITE ( 14 )  'use_surface_fluxes            '
384    WRITE ( 14 )  use_surface_fluxes
385    WRITE ( 14 )  'use_top_fluxes                '
386    WRITE ( 14 )  use_top_fluxes
387    WRITE ( 14 )  'use_ug_for_galilei_tr         '
388    WRITE ( 14 )  use_ug_for_galilei_tr
389    WRITE ( 14 )  'use_upstream_for_tke          '
390    WRITE ( 14 )  use_upstream_for_tke
391    WRITE ( 14 )  'v_init                        '
392    WRITE ( 14 )  v_init
393    WRITE ( 14 )  'v_max                         '
394    WRITE ( 14 )  v_max
395    WRITE ( 14 )  'v_max_ijk                     '
396    WRITE ( 14 )  v_max_ijk
397    WRITE ( 14 )  'vg                            '
398    WRITE ( 14 )  vg
399    WRITE ( 14 )  'vg_surface                    '
400    WRITE ( 14 )  vg_surface
401    WRITE ( 14 )  'vg_vertical_gradient          '
402    WRITE ( 14 )  vg_vertical_gradient
403    WRITE ( 14 )  'vg_vertical_gradient_level    '
404    WRITE ( 14 )  vg_vertical_gradient_level
405    WRITE ( 14 )  'vg_vertical_gradient_level_ind'
406    WRITE ( 14 )  vg_vertical_gradient_level_ind
407    WRITE ( 14 )  'wall_adjustment               '
408    WRITE ( 14 )  wall_adjustment
409    WRITE ( 14 )  'w_max                         '
410    WRITE ( 14 )  w_max
411    WRITE ( 14 )  'w_max_ijk                     '
412    WRITE ( 14 )  w_max_ijk
413    WRITE ( 14 )  'time-series-quantities        '
414    WRITE ( 14 )  cross_ts_uymax, cross_ts_uymax_computed, cross_ts_uymin, &
415                  cross_ts_uymin_computed
416
417!
418!-- Set the end-of-file mark
419    WRITE ( 14 )  '*** end ***                   '
420
421
422 END SUBROUTINE write_var_list
Note: See TracBrowser for help on using the repository browser.