source: palm/trunk/SOURCE/write_var_list.f90 @ 392

Last change on this file since 392 was 392, checked in by raasch, 15 years ago

New:
---

Adapted for machine lck
(mrun, mbuild, subjob)

bc_lr/bc_ns in most subroutines replaced by LOGICAL variables bc_lr_cyc,
bc_ns_cyc for speed optimization
(check_parameters, diffusion_u, diffusion_v, diffusion_w, modules)

Additional timestep criterion in case of simulations with plant canopy (timestep)

Check for illegal entries in section_xy|xz|yz that exceed nz+1|ny+1|nx+1
(check_parameters)

Clipping of dvrp output implemented. Default colourtable for particles
implemented, particle attributes (color, dvrp_size) can be set with new
parameters particle_color, particle_dvrpsize, color_interval,
dvrpsize_interval (init_dvrp, data_output_dvrp, modules, user_data_output_dvrp).
Slicer attributes (dvrp) are set with new routine set_slicer_attributes_dvrp
and are controlled with existing parameters slicer_range_limits.
(set_slicer_attributes_dvrp)

Ocean atmosphere coupling allows to use independent precursor runs in order
to account for different spin-up times. The time when coupling has to be
started is given by new inipar parameter coupling_start_time. The precursor
ocean run has to be started using new mrun option "-y" in order to add
appendix "_O" to all output files.
(check_for_restart, check_parameters, data_output_2d, data_output_3d,
data_output_profiles, data_output_ptseries, data_output_spectra,
data_output_tseries, header, init_coupling, modules, mrun,
parin, read_var_list, surface_coupler, time_integration, write_var_list)

Polygon reduction for topography and ground plate isosurface. Reduction level
for buildings can be chosen with parameter cluster_size. (init_dvrp)

External pressure gradient (check_parameters, header, init_3d_model, modules,
parin, prognostic_equations, read_var_list, write_var_list)

New topography case 'single_street_canyon' (header, init_grid, modules, parin,
read_var_list, user_check_parameters, user_header, user_init_grid, write_var_list)

Option to predefine a target bulk velocity for conserve_volume_flow
(check_parameters, header, init_3d_model, modules, parin, read_var_list,
write_var_list)

Option for user defined 2D data output in xy cross sections at z=nzb+1
(data_output_2d, user_data_output_2d)

xy cross section output of surface heatfluxes (latent, sensible)
(average_3d_data, check_parameters, data_output_2d, modules, read_3d_binary,
sum_up_3d_data, write_3d_binary)

average_3d_data, check_for_restart, check_parameters, data_output_2d, data_output_3d, data_output_dvrp, data_output_profiles, data_output_ptseries, data_output_spectra, data_output_tseries, init_coupling, init_dvrp, init_grid, init_3d_model, header, mbuild, modules, mrun, package_parin, parin, prognostic_equations, read_3d_binary, read_var_list, subjob, surface_coupler, timestep, time_integration, user_check_parameters, user_data_output_2d, user_data_output_dvrp, user_header, user_init_grid, write_3d_binary, write_var_list

New: set_particle_attributes, set_slicer_attributes_dvrp

Changed:


lcmuk changed to lc to avoid problems with Intel compiler on sgi-ice
(poisfft)

For extended NetCDF files, the updated title attribute includes an update of
time_average_text where appropriate. (netcdf)

In case of restart runs without extension, initial profiles are not written
to NetCDF-file anymore. (data_output_profiles, modules, read_var_list, write_var_list)

Small change in formatting of the message handling routine concering the output in the
job protocoll. (message)

initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill', now
independent of turbulent_inflow (check_parameters, header, init_3d_model)

2 NetCDF error numbers changed. (data_output_3d)

A Link to the website appendix_a.html is printed for further information
about the possible errors. (message)

Temperature gradient criterion for estimating the boundary layer height
replaced by the gradient criterion of Sullivan et al. (1998). (flow_statistics)

NetCDF unit attribute in timeseries output in case of statistic regions added
(netcdf)

Output of NetCDF messages with aid of message handling routine.
(check_open, close_file, data_output_2d, data_output_3d,
data_output_profiles, data_output_ptseries, data_output_spectra,
data_output_tseries, netcdf, output_particles_netcdf)

Output of messages replaced by message handling routine.
(advec_particles, advec_s_bc, buoyancy, calc_spectra, check_for_restart,
check_open, coriolis, cpu_log, data_output_2d, data_output_3d, data_output_dvrp,
data_output_profiles, data_output_spectra, fft_xy, flow_statistics, header,
init_1d_model, init_3d_model, init_dvrp, init_grid, init_particles, init_pegrid,
netcdf, parin, plant_canopy_model, poisfft_hybrid, poismg, read_3d_binary,
read_var_list, surface_coupler, temperton_fft, timestep, user_actions,
user_data_output_dvrp, user_dvrp_coltab, user_init_grid, user_init_plant_canopy,
user_parin, user_read_restart_data, user_spectra )

Maximum number of tails is calculated from maximum number of particles and
skip_particles_for_tail (init_particles)

Value of vertical_particle_advection may differ for each particle group
(advec_particles, header, modules)

First constant in array den also defined as type double. (eqn_state_seawater)

Parameter dvrp_psize moved from particles_par to dvrp_graphics_par. (package_parin)

topography_grid_convention moved from userpar to inipar (check_parameters,
header, parin, read_var_list, user_check_parameters, user_header,
user_init_grid, user_parin, write_var_list)

Default value of grid_matching changed to strict.

Adjustments for runs on lcxt4 (necessary due to an software update on CRAY) and
for coupled runs on ibmy (mrun, subjob)

advec_particles, advec_s_bc, buoyancy, calc_spectra, check_for_restart, check_open, check_parameters, close_file, coriolis, cpu_log, data_output_2d, data_output_3d, data_output_dvrp, data_output_profiles, data_output_ptseries, data_output_spectra, data_output_tseries, eqn_state_seawater, fft_xy, flow_statistics, header, init_1d_model, init_3d_model, init_dvrp, init_grid, init_particles, init_pegrid, message, mrun, netcdf, output_particles_netcdf, package_parin, parin, plant_canopy_model, poisfft, poisfft_hybrid, poismg, read_3d_binary, read_var_list, sort_particles, subjob, user_check_parameters, user_header, user_init_grid, user_parin, surface_coupler, temperton_fft, timestep, user_actions, user_data_output_dvrp, user_dvrp_coltab, user_init_grid, user_init_plant_canopy, user_parin, user_read_restart_data, user_spectra, write_var_list

Errors:


Bugfix: Initial hydrostatic pressure profile in case of ocean runs is now
calculated in 5 iteration steps. (init_ocean)

Bugfix: wrong sign in buoyancy production of ocean part in case of not using
the reference density (only in 3D routine production_e) (production_e)

Bugfix: output of averaged 2d/3d quantities requires that an avaraging
interval has been set, respective error message is included (check_parameters)

Bugfix: Output on unit 14 only if requested by write_binary.
(user_last_actions)

Bugfix to avoid zero division by km_neutral (production_e)

Bugfix for extended NetCDF files: In order to avoid 'data mode' errors if
updated attributes are larger than their original size, NF90_PUT_ATT is called
in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a
possible performance loss; an alternative strategy would be to ensure equal
attribute size in a job chain. (netcdf)

Bugfix: correction of initial volume flow for non-flat topography (init_3d_model)
Bugfix: zero initialization of arrays within buildings for 'cyclic_fill' (init_3d_model)

Bugfix: to_be_resorted => s_av for time-averaged scalars (data_output_2d, data_output_3d)

Bugfix: error in formatting the output (message)

Bugfix: avoid that ngp_2dh_s_inner becomes zero (init_3_model)

Typographical error: unit of wpt in dots_unit (modules)

Bugfix: error in check, if particles moved further than one subdomain length.
This check must not be applied for newly released particles. (advec_particles)

Bugfix: several tail counters are initialized, particle_tail_coordinates is
only written to file if its third index is > 0, arrays for tails are allocated
with a minimum size of 10 tails if there is no tail initially (init_particles,
advec_particles)

Bugfix: pressure included for profile output (check_parameters)

Bugfix: Type of count and count_rate changed to default INTEGER on NEC machines
(cpu_log)

Bugfix: output if particle time series only if particle advection is switched
on. (time_integration)

Bugfix: qsws was calculated in case of constant heatflux = .FALSE. (prandtl_fluxes)

Bugfix: averaging along z is not allowed for 2d quantities (e.g. u* and z0) (data_output_2d)

Typographical errors (netcdf)

If the inversion height calculated by the prerun is zero, inflow_damping_height
must be explicitly specified (init_3d_model)

Small bugfix concerning 3d 64bit netcdf output format (header)

Bugfix: dt_fixed removed from the restart file, because otherwise, no change
from a fixed to a variable timestep would be possible in restart runs.
(read_var_list, write_var_list)

Bugfix: initial setting of time_coupling in coupled restart runs (time_integration)

advec_particles, check_parameters, cpu_log, data_output_2d, data_output_3d, header, init_3d_model, init_particles, init_ocean, modules, netcdf, prandtl_fluxes, production_e, read_var_list, time_integration, user_last_actions, write_var_list

  • Property svn:keywords set to Id
File size: 20.0 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 392 2009-09-24 10:39:14Z raasch $
11!
12! 345 2009-07-01 14:37:56Z heinze
13! +output_for_t0
14! bugfix: -dt_fixed, because otherwise, restart runs cannot change from a
15! fixed to a free timestep.
16! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
17! canyon_wall_south, conserve_volume_flow_mode, coupling_start_time,
18! dp_external, dp_level_b, dp_smooth, dpdxy, run_coupled,
19! time_since_reference_point, topography_grid_convention, u_bulk, v_bulk
20!
21! 153 2008-03-19 09:41:30Z steinfeld
22! +cthf, leaf_surface_concentration, scalar_exchange_coefficient
23! +numprocs, hor_index_bounds, inflow_damping_height, inflow_damping_width,
24! mean_inflow_profiles, recycling_width, turbulent_inflow,
25! -cross_ts_*, npex, npey
26! hom_sum, volume_flow_area, volume_flow_initial moved from write_3d_binary
27! to here
28!
29! 138 2007-11-28 10:03:58Z letzel
30! +canopy_mode, drag_coefficient, lad, lad_surface, lad_vertical_gradient,
31! lad_vertical_gradient_level, lad_vertical_gradient_level_ind, pch_index,
32! plant_canopy, time_sort_particles
33!
34! 102 2007-07-27 09:09:17Z raasch
35! +top_momentumflux_u|v, time_coupling
36!
37! 95 2007-06-02 16:48:38Z raasch
38! +bc_sa_t, ocean, sa_init, sa_surface, sa_vertical_gradient,
39! sa_vertical_gradient_level, bottom/top_salinity_flux
40!
41! 87 2007-05-22 15:46:47Z raasch
42! +max_pr_user (version 3.1)
43!
44! 75 2007-03-22 09:54:05Z raasch
45! +loop_optimization, pt_refrence, moisture renamed humidity
46!
47! 20 2007-02-26 00:12:32Z raasch
48! +top_heatflux, use_top_fluxes
49!
50! RCS Log replace by Id keyword, revision history cleaned up
51!
52! Revision 1.34  2006/08/22 14:30:52  raasch
53! +dz_max
54!
55! Revision 1.1  1998/03/18 20:20:38  raasch
56! Initial revision
57!
58!
59! Description:
60! ------------
61! Writing values of control variables to restart-file (binary format).
62! These informations are only written to the file opened by PE0.
63!------------------------------------------------------------------------------!
64
65    USE arrays_3d
66    USE averaging
67    USE control_parameters
68    USE grid_variables
69    USE indices
70    USE model_1d
71    USE netcdf_control
72    USE particle_attributes
73    USE pegrid
74    USE profil_parameter
75    USE statistics
76
77    IMPLICIT NONE
78
79    CHARACTER (LEN=10) ::  binary_version
80
81
82    binary_version = '3.4'
83
84    WRITE ( 14 )  binary_version
85
86    WRITE ( 14 )  'numprocs                      '
87    WRITE ( 14 )  numprocs
88    WRITE ( 14 )  'hor_index_bounds              '
89    WRITE ( 14 )  hor_index_bounds
90    WRITE ( 14 )  'nz                            '
91    WRITE ( 14 )  nz
92    WRITE ( 14 )  'max_pr_user                   '
93    WRITE ( 14 )  max_pr_user
94    WRITE ( 14 )  'statistic_regions             '
95    WRITE ( 14 )  statistic_regions
96
97!
98!-- Caution: After changes in the following parameter-list, the
99!-- -------  version number stored in the variable binary_version has to be
100!--          increased. The same changes must also be done in the parameter-
101!--          list in read_var_list.
102
103    WRITE ( 14 )  'adjust_mixing_length          '
104    WRITE ( 14 )  adjust_mixing_length
105    WRITE ( 14 )  'advected_distance_x           '
106    WRITE ( 14 )  advected_distance_x
107    WRITE ( 14 )  'advected_distance_y           '
108    WRITE ( 14 )  advected_distance_y
109    WRITE ( 14 )  'alpha_surface                 '
110    WRITE ( 14 )  alpha_surface
111    WRITE ( 14 )  'average_count_pr              '
112    WRITE ( 14 )  average_count_pr
113    WRITE ( 14 )  'average_count_sp              '
114    WRITE ( 14 )  average_count_sp
115    WRITE ( 14 )  'average_count_3d              '
116    WRITE ( 14 )  average_count_3d
117    WRITE ( 14 )  'bc_e_b                        '
118    WRITE ( 14 )  bc_e_b
119    WRITE ( 14 )  'bc_lr                         '
120    WRITE ( 14 )  bc_lr
121    WRITE ( 14 )  'bc_ns                         '
122    WRITE ( 14 )  bc_ns
123    WRITE ( 14 )  'bc_p_b                        '
124    WRITE ( 14 )  bc_p_b
125    WRITE ( 14 )  'bc_p_t                        '
126    WRITE ( 14 )  bc_p_t
127    WRITE ( 14 )  'bc_pt_b                       '
128    WRITE ( 14 )  bc_pt_b
129    WRITE ( 14 )  'bc_pt_t                       '
130    WRITE ( 14 )  bc_pt_t
131    WRITE ( 14 )  'bc_pt_t_val                   '
132    WRITE ( 14 )  bc_pt_t_val
133    WRITE ( 14 )  'bc_q_b                        '
134    WRITE ( 14 )  bc_q_b
135    WRITE ( 14 )  'bc_q_t                        '
136    WRITE ( 14 )  bc_q_t
137    WRITE ( 14 )  'bc_q_t_val                    '
138    WRITE ( 14 )  bc_q_t_val
139    WRITE ( 14 )  'bc_s_b                        '
140    WRITE ( 14 )  bc_s_b
141    WRITE ( 14 )  'bc_s_t                        '
142    WRITE ( 14 )  bc_s_t
143    WRITE ( 14 )  'bc_sa_t                       '
144    WRITE ( 14 )  bc_sa_t
145    WRITE ( 14 )  'bc_uv_b                       '
146    WRITE ( 14 )  bc_uv_b
147    WRITE ( 14 )  'bc_uv_t                       '
148    WRITE ( 14 )  bc_uv_t
149    WRITE ( 14 )  'bottom_salinityflux           '
150    WRITE ( 14 )  bottom_salinityflux
151    WRITE ( 14 )  'building_height               '
152    WRITE ( 14 )  building_height
153    WRITE ( 14 )  'building_length_x             '
154    WRITE ( 14 )  building_length_x
155    WRITE ( 14 )  'building_length_y             '
156    WRITE ( 14 )  building_length_y
157    WRITE ( 14 )  'building_wall_left            '
158    WRITE ( 14 )  building_wall_left
159    WRITE ( 14 )  'building_wall_south           '
160    WRITE ( 14 )  building_wall_south
161    WRITE ( 14 )  'canopy_mode                   '
162    WRITE ( 14 )  canopy_mode
163    WRITE ( 14 )  'canyon_height                 '
164    WRITE ( 14 )  canyon_height
165    WRITE ( 14 )  'canyon_width_x                '
166    WRITE ( 14 )  canyon_width_x
167    WRITE ( 14 )  'canyon_width_y                '
168    WRITE ( 14 )  canyon_width_y
169    WRITE ( 14 )  'canyon_wall_left              '
170    WRITE ( 14 )  canyon_wall_left
171    WRITE ( 14 )  'canyon_wall_south             '
172    WRITE ( 14 )  canyon_wall_south
173    WRITE ( 14 )  'cloud_droplets                '
174    WRITE ( 14 )  cloud_droplets
175    WRITE ( 14 )  'cloud_physics                 '
176    WRITE ( 14 )  cloud_physics
177    WRITE ( 14 )  'conserve_volume_flow          '
178    WRITE ( 14 )  conserve_volume_flow
179    WRITE ( 14 )  'conserve_volume_flow_mode     '
180    WRITE ( 14 )  conserve_volume_flow_mode
181    WRITE ( 14 )  'coupling_start_time           '
182    WRITE ( 14 )  coupling_start_time
183    WRITE ( 14 )  'current_timestep_number       '
184    WRITE ( 14 )  current_timestep_number
185    WRITE ( 14 )  'cthf                          '
186    WRITE ( 14 )  cthf
187    WRITE ( 14 )  'cut_spline_overshoot          '
188    WRITE ( 14 )  cut_spline_overshoot
189    WRITE ( 14 )  'damp_level_1d                 '
190    WRITE ( 14 )  damp_level_1d
191    WRITE ( 14 )  'dissipation_1d                '
192    WRITE ( 14 )  dissipation_1d
193    WRITE ( 14 )  'dp_external                   '
194    WRITE ( 14 )  dp_external
195    WRITE ( 14 )  'dp_level_b                    '
196    WRITE ( 14 )  dp_level_b
197    WRITE ( 14 )  'dp_smooth                     '
198    WRITE ( 14 )  dp_smooth
199    WRITE ( 14 )  'dpdxy                         '
200    WRITE ( 14 )  dpdxy
201    WRITE ( 14 )  'drag_coefficient              '
202    WRITE ( 14 )  drag_coefficient
203    WRITE ( 14 )  'dt_pr_1d                      '
204    WRITE ( 14 )  dt_pr_1d
205    WRITE ( 14 )  'dt_run_control_1d             '
206    WRITE ( 14 )  dt_run_control_1d
207    WRITE ( 14 )  'dt_3d                         '
208    WRITE ( 14 )  dt_3d
209    WRITE ( 14 )  'dvrp_filecount                '
210    WRITE ( 14 )  dvrp_filecount
211    WRITE ( 14 )  'dx                            '
212    WRITE ( 14 )  dx
213    WRITE ( 14 )  'dy                            '
214    WRITE ( 14 )  dy
215    WRITE ( 14 )  'dz                            '
216    WRITE ( 14 )  dz
217    WRITE ( 14 )  'dz_max                        '
218    WRITE ( 14 )  dz_max
219    WRITE ( 14 )  'dz_stretch_factor             '
220    WRITE ( 14 )  dz_stretch_factor
221    WRITE ( 14 )  'dz_stretch_level              '
222    WRITE ( 14 )  dz_stretch_level
223    WRITE ( 14 )  'e_min                         '
224    WRITE ( 14 )  e_min
225    WRITE ( 14 )  'end_time_1d                   '
226    WRITE ( 14 )  end_time_1d
227    WRITE ( 14 )  'fft_method                    '
228    WRITE ( 14 )  fft_method
229    WRITE ( 14 )  'first_call_advec_particles    '
230    WRITE ( 14 )  first_call_advec_particles
231    WRITE ( 14 )  'galilei_transformation        '
232    WRITE ( 14 )  galilei_transformation
233    WRITE ( 14 )  'grid_matching                 '
234    WRITE ( 14 )  grid_matching
235    WRITE ( 14 )  'hom                           '
236    WRITE ( 14 )  hom
237    WRITE ( 14 )  'hom_sum                       '
238    WRITE ( 14 )  hom_sum
239    WRITE ( 14 )  'humidity                      '
240    WRITE ( 14 )  humidity
241    IF ( ALLOCATED( inflow_damping_factor ) )  THEN
242       WRITE ( 14 )  'inflow_damping_factor         '
243       WRITE ( 14 )  inflow_damping_factor
244    ENDIF
245    WRITE ( 14 )  'inflow_damping_height         '
246    WRITE ( 14 )  inflow_damping_height
247    WRITE ( 14 )  'inflow_damping_width          '
248    WRITE ( 14 )  inflow_damping_width
249    WRITE ( 14 )  'inflow_disturbance_begin      '
250    WRITE ( 14 )  inflow_disturbance_begin
251    WRITE ( 14 )  'inflow_disturbance_end        '
252    WRITE ( 14 )  inflow_disturbance_end
253    WRITE ( 14 )  'km_constant                   '
254    WRITE ( 14 )  km_constant
255    WRITE ( 14 )  'km_damp_max                   '
256    WRITE ( 14 )  km_damp_max
257    WRITE ( 14 )  'lad                           '
258    WRITE ( 14 )  lad
259    WRITE ( 14 )  'lad_surface                   '
260    WRITE ( 14 )  lad_surface
261    WRITE ( 14 )  'lad_vertical_gradient         '
262    WRITE ( 14 )  lad_vertical_gradient
263    WRITE ( 14 )  'lad_vertical_gradient_level   '
264    WRITE ( 14 )  lad_vertical_gradient_level
265    WRITE ( 14 )  'lad_vertical_gradient_level_in'
266    WRITE ( 14 )  lad_vertical_gradient_level_ind
267    WRITE ( 14 )  'last_dt_change                '
268    WRITE ( 14 )  last_dt_change
269    WRITE ( 14 )  'leaf_surface_concentration    '
270    WRITE ( 14 )  leaf_surface_concentration
271    WRITE ( 14 )  'long_filter_factor            '
272    WRITE ( 14 )  long_filter_factor
273    WRITE ( 14 )  'loop_optimization             '
274    WRITE ( 14 )  loop_optimization
275    IF ( ALLOCATED( mean_inflow_profiles ) )  THEN
276       WRITE ( 14 )  'mean_inflow_profiles          '
277       WRITE ( 14 )  mean_inflow_profiles
278    ENDIF
279    WRITE ( 14 )  'mixing_length_1d              '
280    WRITE ( 14 )  mixing_length_1d
281    WRITE ( 14 )  'momentum_advec                '
282    WRITE ( 14 )  momentum_advec
283    WRITE ( 14 )  'netcdf_precision              '
284    WRITE ( 14 )  netcdf_precision
285    WRITE ( 14 )  'nsor_ini                      '
286    WRITE ( 14 )  nsor_ini
287    WRITE ( 14 )  'nx                            '
288    WRITE ( 14 )  nx
289    WRITE ( 14 )  'ny                            '
290    WRITE ( 14 )  ny
291    WRITE ( 14 )  'ocean                         '
292    WRITE ( 14 )  ocean
293    WRITE ( 14 )  'old_dt                        '
294    WRITE ( 14 )  old_dt
295    WRITE ( 14 )  'omega                         '
296    WRITE ( 14 )  omega
297    WRITE ( 14 )  'outflow_damping_width         '
298    WRITE ( 14 )  outflow_damping_width
299    WRITE ( 14 )  'output_for_t0                 '
300    WRITE ( 14 )  output_for_t0
301    WRITE ( 14 )  'overshoot_limit_e             '
302    WRITE ( 14 )  overshoot_limit_e
303    WRITE ( 14 )  'overshoot_limit_pt            '
304    WRITE ( 14 )  overshoot_limit_pt
305    WRITE ( 14 )  'overshoot_limit_u             '
306    WRITE ( 14 )  overshoot_limit_u
307    WRITE ( 14 )  'overshoot_limit_v             '
308    WRITE ( 14 )  overshoot_limit_v
309    WRITE ( 14 )  'overshoot_limit_w             '
310    WRITE ( 14 )  overshoot_limit_w
311    WRITE ( 14 )  'passive_scalar                '
312    WRITE ( 14 )  passive_scalar
313    WRITE ( 14 )  'pch_index                     '
314    WRITE ( 14 )  pch_index
315    WRITE ( 14 )  'phi                           '
316    WRITE ( 14 )  phi
317    WRITE ( 14 )  'plant_canopy                  '
318    WRITE ( 14 )  plant_canopy
319    WRITE ( 14 )  'prandtl_layer                 '
320    WRITE ( 14 )  prandtl_layer
321    WRITE ( 14 )  'precipitation                 '
322    WRITE ( 14 )  precipitation
323    WRITE ( 14 )  'pt_init                       '
324    WRITE ( 14 )  pt_init
325    WRITE ( 14 )  'pt_reference                  '
326    WRITE ( 14 )  pt_reference
327    WRITE ( 14 )  'pt_surface                    '
328    WRITE ( 14 )  pt_surface
329    WRITE ( 14 )  'pt_surface_initial_change     '
330    WRITE ( 14 )  pt_surface_initial_change
331    WRITE ( 14 )  'pt_vertical_gradient          '
332    WRITE ( 14 )  pt_vertical_gradient
333    WRITE ( 14 )  'pt_vertical_gradient_level    '
334    WRITE ( 14 )  pt_vertical_gradient_level
335    WRITE ( 14 )  'pt_vertical_gradient_level_ind'
336    WRITE ( 14 )  pt_vertical_gradient_level_ind
337    WRITE ( 14 )  'q_init                        '
338    WRITE ( 14 )  q_init
339    WRITE ( 14 )  'q_surface                     '
340    WRITE ( 14 )  q_surface
341    WRITE ( 14 )  'q_surface_initial_change      '
342    WRITE ( 14 )  q_surface_initial_change
343    WRITE ( 14 )  'q_vertical_gradient           '
344    WRITE ( 14 )  q_vertical_gradient
345    WRITE ( 14 )  'q_vertical_gradient_level     '
346    WRITE ( 14 )  q_vertical_gradient_level
347    WRITE ( 14 )  'q_vertical_gradient_level_ind '
348    WRITE ( 14 )  q_vertical_gradient_level_ind
349    WRITE ( 14 )  'radiation                     '
350    WRITE ( 14 )  radiation
351    WRITE ( 14 )  'random_generator              '
352    WRITE ( 14 )  random_generator
353    WRITE ( 14 )  'random_heatflux               '
354    WRITE ( 14 )  random_heatflux
355    WRITE ( 14 )  'recycling_width               '
356    WRITE ( 14 )  recycling_width
357    WRITE ( 14 )  'rif_max                       '
358    WRITE ( 14 )  rif_max
359    WRITE ( 14 )  'rif_min                       '
360    WRITE ( 14 )  rif_min
361    WRITE ( 14 )  'roughness_length              '
362    WRITE ( 14 )  roughness_length
363    WRITE ( 14 )  'runnr                         '
364    WRITE ( 14 )  runnr
365    WRITE ( 14 )  'run_coupled                   '
366    WRITE ( 14 )  run_coupled
367    WRITE ( 14 )  'sa_init                       '
368    WRITE ( 14 )  sa_init
369    WRITE ( 14 )  'sa_surface                    '
370    WRITE ( 14 )  sa_surface
371    WRITE ( 14 )  'sa_vertical_gradient          '
372    WRITE ( 14 )  sa_vertical_gradient
373    WRITE ( 14 )  'sa_vertical_gradient_level    '
374    WRITE ( 14 )  sa_vertical_gradient_level
375    WRITE ( 14 )  'scalar_advec                  '
376    WRITE ( 14 )  scalar_advec
377    WRITE ( 14 )  'scalar_exchange_coefficient   '
378    WRITE ( 14 )  scalar_exchange_coefficient
379    WRITE ( 14 )  'simulated_time                '
380    WRITE ( 14 )  simulated_time
381    WRITE ( 14 )  'surface_heatflux              '
382    WRITE ( 14 )  surface_heatflux
383    WRITE ( 14 )  'surface_pressure              '
384    WRITE ( 14 )  surface_pressure
385    WRITE ( 14 )  'surface_scalarflux            '
386    WRITE ( 14 )  surface_scalarflux   
387    WRITE ( 14 )  'surface_waterflux             '
388    WRITE ( 14 )  surface_waterflux   
389    WRITE ( 14 )  's_surface                     '
390    WRITE ( 14 )  s_surface
391    WRITE ( 14 )  's_surface_initial_change      '
392    WRITE ( 14 )  s_surface_initial_change
393    WRITE ( 14 )  's_vertical_gradient           '
394    WRITE ( 14 )  s_vertical_gradient
395    WRITE ( 14 )  's_vertical_gradient_level     '
396    WRITE ( 14 )  s_vertical_gradient_level
397    WRITE ( 14 )  'time_coupling                 '
398    WRITE ( 14 )  time_coupling
399    WRITE ( 14 )  'time_disturb                  '
400    WRITE ( 14 )  time_disturb
401    WRITE ( 14 )  'time_dopr                     '
402    WRITE ( 14 )  time_dopr
403    WRITE ( 14 )  'time_dopr_av                  '
404    WRITE ( 14 )  time_dopr_av
405    WRITE ( 14 )  'time_dopr_listing             '
406    WRITE ( 14 )  time_dopr_listing
407    WRITE ( 14 )  'time_dopts                    '
408    WRITE ( 14 )  time_dopts
409    WRITE ( 14 )  'time_dosp                     '
410    WRITE ( 14 )  time_dosp
411    WRITE ( 14 )  'time_dots                     '
412    WRITE ( 14 )  time_dots
413    WRITE ( 14 )  'time_do2d_xy                  '
414    WRITE ( 14 )  time_do2d_xy
415    WRITE ( 14 )  'time_do2d_xz                  '
416    WRITE ( 14 )  time_do2d_xz
417    WRITE ( 14 )  'time_do2d_yz                  '
418    WRITE ( 14 )  time_do2d_yz
419    WRITE ( 14 )  'time_do3d                     '
420    WRITE ( 14 )  time_do3d
421    WRITE ( 14 )  'time_do_av                    '
422    WRITE ( 14 )  time_do_av
423    WRITE ( 14 )  'time_do_sla                   '
424    WRITE ( 14 )  time_do_sla
425    WRITE ( 14 )  'time_dvrp                     '
426    WRITE ( 14 )  time_dvrp
427    WRITE ( 14 )  'time_restart                  '
428    WRITE ( 14 )  time_restart
429    WRITE ( 14 )  'time_run_control              '
430    WRITE ( 14 )  time_run_control
431    WRITE ( 14 )  'time_since_reference_point    '
432    WRITE ( 14 )  time_since_reference_point
433    WRITE ( 14 )  'time_sort_particles           '
434    WRITE ( 14 )  time_sort_particles
435    WRITE ( 14 )  'timestep_scheme               '
436    WRITE ( 14 )  timestep_scheme
437    WRITE ( 14 )  'topography                    '
438    WRITE ( 14 )  topography
439    WRITE ( 14 )  'topography_grid_convention    '
440    WRITE ( 14 )  topography_grid_convention
441    WRITE ( 14 )  'top_heatflux                  '
442    WRITE ( 14 )  top_heatflux
443    WRITE ( 14 )  'top_momentumflux_u            '
444    WRITE ( 14 )  top_momentumflux_u
445    WRITE ( 14 )  'top_momentumflux_v            '
446    WRITE ( 14 )  top_momentumflux_v
447    WRITE ( 14 )  'top_salinityflux              '
448    WRITE ( 14 )  top_salinityflux
449    WRITE ( 14 )  'tsc                           '
450    WRITE ( 14 )  tsc
451    WRITE ( 14 )  'turbulent_inflow              '
452    WRITE ( 14 )  turbulent_inflow
453    WRITE ( 14 )  'u_bulk                        '
454    WRITE ( 14 )  u_bulk
455    WRITE ( 14 )  'u_init                        '
456    WRITE ( 14 )  u_init
457    WRITE ( 14 )  'u_max                         '
458    WRITE ( 14 )  u_max
459    WRITE ( 14 )  'u_max_ijk                     '
460    WRITE ( 14 )  u_max_ijk
461    WRITE ( 14 )  'ug                            '
462    WRITE ( 14 )  ug
463    WRITE ( 14 )  'ug_surface                    '
464    WRITE ( 14 )  ug_surface
465    WRITE ( 14 )  'ug_vertical_gradient          '
466    WRITE ( 14 )  ug_vertical_gradient
467    WRITE ( 14 )  'ug_vertical_gradient_level    '
468    WRITE ( 14 )  ug_vertical_gradient_level
469    WRITE ( 14 )  'ug_vertical_gradient_level_ind'
470    WRITE ( 14 )  ug_vertical_gradient_level_ind
471    WRITE ( 14 )  'ups_limit_e                   '
472    WRITE ( 14 )  ups_limit_e
473    WRITE ( 14 )  'ups_limit_pt                  '
474    WRITE ( 14 )  ups_limit_pt
475    WRITE ( 14 )  'ups_limit_u                   '
476    WRITE ( 14 )  ups_limit_u
477    WRITE ( 14 )  'ups_limit_v                   '
478    WRITE ( 14 )  ups_limit_v
479    WRITE ( 14 )  'ups_limit_w                   '
480    WRITE ( 14 )  ups_limit_w
481    WRITE ( 14 )  'use_surface_fluxes            '
482    WRITE ( 14 )  use_surface_fluxes
483    WRITE ( 14 )  'use_top_fluxes                '
484    WRITE ( 14 )  use_top_fluxes
485    WRITE ( 14 )  'use_ug_for_galilei_tr         '
486    WRITE ( 14 )  use_ug_for_galilei_tr
487    WRITE ( 14 )  'use_upstream_for_tke          '
488    WRITE ( 14 )  use_upstream_for_tke
489    WRITE ( 14 )  'v_bulk                        '
490    WRITE ( 14 )  v_bulk
491    WRITE ( 14 )  'v_init                        '
492    WRITE ( 14 )  v_init
493    WRITE ( 14 )  'v_max                         '
494    WRITE ( 14 )  v_max
495    WRITE ( 14 )  'v_max_ijk                     '
496    WRITE ( 14 )  v_max_ijk
497    WRITE ( 14 )  'vg                            '
498    WRITE ( 14 )  vg
499    WRITE ( 14 )  'vg_surface                    '
500    WRITE ( 14 )  vg_surface
501    WRITE ( 14 )  'vg_vertical_gradient          '
502    WRITE ( 14 )  vg_vertical_gradient
503    WRITE ( 14 )  'vg_vertical_gradient_level    '
504    WRITE ( 14 )  vg_vertical_gradient_level
505    WRITE ( 14 )  'vg_vertical_gradient_level_ind'
506    WRITE ( 14 )  vg_vertical_gradient_level_ind
507    WRITE ( 14 )  'volume_flow_area              '
508    WRITE ( 14 )  volume_flow_area
509    WRITE ( 14 )  'volume_flow_initial           '
510    WRITE ( 14 )  volume_flow_initial
511    WRITE ( 14 )  'wall_adjustment               '
512    WRITE ( 14 )  wall_adjustment
513    WRITE ( 14 )  'w_max                         '
514    WRITE ( 14 )  w_max
515    WRITE ( 14 )  'w_max_ijk                     '
516    WRITE ( 14 )  w_max_ijk
517
518!
519!-- Set the end-of-file mark
520    WRITE ( 14 )  '*** end ***                   '
521
522
523 END SUBROUTINE write_var_list
Note: See TracBrowser for help on using the repository browser.