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

Last change on this file since 243 was 139, checked in by raasch, 16 years ago

New:
---

Plant canopy model of Watanabe (2004,BLM 112,307-341) added.
It can be switched on by the inipar parameter plant_canopy.
The inipar parameter canopy_mode can be used to prescribe a
plant canopy type. The default case is a homogeneous plant
canopy. Heterogeneous distributions of the leaf area
density and the canopy drag coefficient can be defined in the
new routine user_init_plant_canopy (user_interface).
The inipar parameters lad_surface, lad_vertical_gradient and
lad_vertical_gradient_level can be used in order to
prescribe the vertical profile of leaf area density. The
inipar parameter drag_coefficient determines the canopy
drag coefficient.
Finally, the inipar parameter pch_index determines the
index of the upper boundary of the plant canopy.

Allow new case bc_uv_t = 'dirichlet_0' for channel flow.

For unknown variables (CASE DEFAULT) call new subroutine user_data_output_dvrp

Pressure boundary conditions for vertical walls added to the multigrid solver.
They are applied using new wall flag arrays (wall_flags_..) which are defined
for each grid level. New argument gls added to routine user_init_grid
(user_interface).

Frequence of sorting particles can be controlled with new particles_par
parameter dt_sort_particles. Sorting is moved from the SGS timestep loop in
advec_particles after the end of this loop.

advec_particles, check_parameters, data_output_dvrp, header, init_3d_model, init_grid, init_particles, init_pegrid, modules, package_parin, parin, plant_canopy_model, read_var_list, read_3d_binary, user_interface, write_var_list, write_3d_binary

Changed:


Redefine initial nzb_local as the actual total size of topography (later the
extent of topography in nzb_local is reduced by 1dx at the E topography walls
and by 1dy at the N topography walls to form the basis for nzb_s_inner);
for consistency redefine 'single_building' case.

Vertical profiles now based on nzb_s_inner; they are divided by
ngp_2dh_s_inner (scalars, procucts of scalars) and ngp_2dh (staggered velocity
components and their products, procucts of scalars and velocity components),
respectively.

Allow two instead of one digit to specify isosurface and slicer variables.

Status of 3D-volume NetCDF data file only depends on switch netcdf_64bit_3d (check_open)

prognostic_equations include the respective wall_*flux in the parameter list of
calls of diffusion_s. Same as before, only the values of wall_heatflux(0:4)
can be assigned. At present, wall_humidityflux, wall_qflux, wall_salinityflux,
and wall_scalarflux are kept zero. diffusion_s uses the respective wall_*flux
instead of wall_heatflux. This update serves two purposes:

  • it avoids errors in calculations with humidity/scalar/salinity and prescribed

non-zero wall_heatflux,

  • it prepares PALM for a possible assignment of wall fluxes of

humidity/scalar/salinity in a future release.

buoyancy, check_open, data_output_dvrp, diffusion_s, diffusivities, flow_statistics, header, init_3d_model, init_dvrp, init_grid, modules, prognostic_equations

Errors:


Bugfix: summation of sums_l_l in diffusivities.

Several bugfixes in the ocean part: Initial density rho is calculated
(init_ocean). Error in initializing u_init and v_init removed
(check_parameters). Calculation of density flux now starts from
nzb+1 (production_e).

Bugfix: pleft/pright changed to pnorth/psouth in sendrecv of particle tail
numbers along y, small bugfixes in the SGS part (advec_particles)

Bugfix: model_string needed a default value (combine_plot_fields)

Bugfix: wavenumber calculation for even nx in routines maketri (poisfft)

Bugfix: assignment of fluxes at walls

Bugfix: absolute value of f must be used when calculating the Blackadar mixing length (init_1d_model)

advec_particles, check_parameters, combine_plot_fields, diffusion_s, diffusivities, init_ocean, init_1d_model, poisfft, production_e

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