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

Last change on this file since 1179 was 1179, checked in by raasch, 11 years ago

New:
---
Initial profiles can be used as reference state in the buoyancy term. New parameter
reference_state introduced. Calculation and handling of reference state in buoyancy term revised.
binary version for restart files changed from 3.9 to 3.9a (no downward compatibility!),
initial profile for rho added to hom (id=77)

Errors:


small bugfix for background communication (time_integration)

  • Property svn:keywords set to Id
File size: 24.5 KB
Line 
1 SUBROUTINE write_var_list
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! +reference_state, ref_state
23!
24! Former revisions:
25! -----------------
26! $Id: write_var_list.f90 1179 2013-06-14 05:57:58Z raasch $
27!
28! 1115 2013-03-26 18:16:16Z hoffmann
29! unused variables removed
30!
31! 1065 2012-11-22 17:42:36Z hoffmann
32! +nc, c_sedimentation, turbulence, limiter_sedimentation
33! -mu_constant, mu_constant_value
34!
35! 1053 2012-11-13 17:11:03Z hoffmann
36! necessary expansions according to the two new prognostic equations (nr, qr)
37! of the two-moment cloud physics scheme:
38! +bc_*_b, bc_*_t, bc_*_t_val, *_init, *_surface, *_surface_initial_change,
39! +*_vertical_gradient, *_vertical_gradient_level, *_vertical_gradient_level_ind,
40! +surface_waterflux_*
41!
42! in addition, steering parameters parameters of the two-moment cloud physics
43! scheme:   
44! +cloud_scheme, +drizzle, +mu_constant, +mu_constant_value, +ventilation_effect
45!
46! 1036 2012-10-22 13:43:42Z raasch
47! code put under GPL (PALM 3.9)
48!
49! 1015 2012-09-27 09:23:24Z raasch
50! -adjust_mixing_length
51!
52! 1003 2012-09-14 14:35:53Z raasch
53! -grid_matching
54!
55! 1001 2012-09-13 14:08:46Z raasch
56! -cut_spline_overshoot, last_dt_change, long_filter_factor, overshoot_limit_*,
57! ups_limit_*
58!
59! 978 2012-08-09 08:28:32Z fricke
60! -km_damp_max, outflow_damping_width
61! +pt_damping_factor, pt_damping_width
62! +z0h_factor
63!
64! 940 2012-07-09 14:31:00Z raasch
65! +neutral
66!
67! 927 2012-06-06 19:15:04Z raasch
68! +masking_method
69!
70! 849 2012-03-15 10:35:09Z raasch
71! first_call_advec_particles renamed first_call_lpm
72!
73! 824 2012-02-17 09:09:57Z raasch
74! +curvature_solution_effects
75!
76! 622 2010-12-10 08:08:13Z raasch
77! +collective_wait
78!
79! 600 2010-11-24 16:10:51Z raasch
80! +call_psolver_at_all_substeps, cfl_factor, cycle_mg, mg_cycles,
81! mg_switch_to_pe0_level, ngsrb, nsor, omega_sor, psolver,
82! rayleigh_damping_factor, rayleigh_damping_height, residual_limit
83!
84! 589 2010-10-27 14:21:29Z heinze
85! bugfix: character string of subs_vertical_gradient and
86! subs_vertical_gradient_level shortened to 30 characters
87!
88! 587 2010-10-27 08:36:51Z helmke
89! +time_domask
90!
91! 580 2010-10-05 13:59:11Z heinze
92! Renaming of ws_vertical_gradient to subs_vertical_gradient,
93! ws_vertical_gradient_level to subs_vertical_gradient_level and
94! ws_vertical_gradient_level_ind to subs_vertical_gradient_level_i
95!
96! 411 2009-12-11 14:15:58Z heinze
97! +large_scale_subsidence, ws_vertical_gradient, ws_vertical_gradient_level,
98! ws_vertical_gradient_level_ind
99!
100! 345 2009-07-01 14:37:56Z heinze
101! +output_for_t0
102! bugfix: -dt_fixed, because otherwise, restart runs cannot change from a
103! fixed to a free timestep.
104! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
105! canyon_wall_south, conserve_volume_flow_mode, coupling_start_time,
106! dp_external, dp_level_b, dp_smooth, dpdxy, run_coupled,
107! time_since_reference_point, topography_grid_convention, u_bulk, v_bulk
108!
109! 153 2008-03-19 09:41:30Z steinfeld
110! +cthf, leaf_surface_concentration, scalar_exchange_coefficient
111! +numprocs, hor_index_bounds, inflow_damping_height, inflow_damping_width,
112! mean_inflow_profiles, recycling_width, turbulent_inflow,
113! -cross_ts_*, npex, npey
114! hom_sum, volume_flow_area, volume_flow_initial moved from write_3d_binary
115! to here
116!
117! 138 2007-11-28 10:03:58Z letzel
118! +canopy_mode, drag_coefficient, lad, lad_surface, lad_vertical_gradient,
119! lad_vertical_gradient_level, lad_vertical_gradient_level_ind, pch_index,
120! plant_canopy, time_sort_particles
121!
122! 102 2007-07-27 09:09:17Z raasch
123! +top_momentumflux_u|v, time_coupling
124!
125! 95 2007-06-02 16:48:38Z raasch
126! +bc_sa_t, ocean, sa_init, sa_surface, sa_vertical_gradient,
127! sa_vertical_gradient_level, bottom/top_salinity_flux
128!
129! 87 2007-05-22 15:46:47Z raasch
130! +max_pr_user (version 3.1)
131!
132! 75 2007-03-22 09:54:05Z raasch
133! +loop_optimization, pt_refrence, moisture renamed humidity
134!
135! 20 2007-02-26 00:12:32Z raasch
136! +top_heatflux, use_top_fluxes
137!
138! RCS Log replace by Id keyword, revision history cleaned up
139!
140! Revision 1.34  2006/08/22 14:30:52  raasch
141! +dz_max
142!
143! Revision 1.1  1998/03/18 20:20:38  raasch
144! Initial revision
145!
146!
147! Description:
148! ------------
149! Writing values of control variables to restart-file (binary format).
150! These informations are only written to the file opened by PE0.
151!------------------------------------------------------------------------------!
152
153    USE arrays_3d
154    USE averaging
155    USE cloud_parameters
156    USE control_parameters
157    USE grid_variables
158    USE indices
159    USE model_1d
160    USE netcdf_control
161    USE particle_attributes
162    USE pegrid
163    USE profil_parameter
164    USE statistics
165
166    IMPLICIT NONE
167
168    CHARACTER (LEN=10) ::  binary_version
169
170
171    binary_version = '3.9a'
172
173    WRITE ( 14 )  binary_version
174
175    WRITE ( 14 )  'numprocs                      '
176    WRITE ( 14 )  numprocs
177    WRITE ( 14 )  'hor_index_bounds              '
178    WRITE ( 14 )  hor_index_bounds
179    WRITE ( 14 )  'nz                            '
180    WRITE ( 14 )  nz
181    WRITE ( 14 )  'max_pr_user                   '
182    WRITE ( 14 )  max_pr_user
183    WRITE ( 14 )  'statistic_regions             '
184    WRITE ( 14 )  statistic_regions
185
186!
187!-- Caution: After changes in the following parameter-list, the
188!-- -------  version number stored in the variable binary_version has to be
189!--          increased. The same changes must also be done in the parameter-
190!--          list in read_var_list.
191
192    WRITE ( 14 )  'advected_distance_x           '
193    WRITE ( 14 )  advected_distance_x
194    WRITE ( 14 )  'advected_distance_y           '
195    WRITE ( 14 )  advected_distance_y
196    WRITE ( 14 )  'alpha_surface                 '
197    WRITE ( 14 )  alpha_surface
198    WRITE ( 14 )  'average_count_pr              '
199    WRITE ( 14 )  average_count_pr
200    WRITE ( 14 )  'average_count_sp              '
201    WRITE ( 14 )  average_count_sp
202    WRITE ( 14 )  'average_count_3d              '
203    WRITE ( 14 )  average_count_3d
204    WRITE ( 14 )  'bc_e_b                        '
205    WRITE ( 14 )  bc_e_b
206    WRITE ( 14 )  'bc_lr                         '
207    WRITE ( 14 )  bc_lr
208    WRITE ( 14 )  'bc_ns                         '
209    WRITE ( 14 )  bc_ns
210    WRITE ( 14 )  'bc_p_b                        '
211    WRITE ( 14 )  bc_p_b
212    WRITE ( 14 )  'bc_p_t                        '
213    WRITE ( 14 )  bc_p_t
214    WRITE ( 14 )  'bc_pt_b                       '
215    WRITE ( 14 )  bc_pt_b
216    WRITE ( 14 )  'bc_pt_t                       '
217    WRITE ( 14 )  bc_pt_t
218    WRITE ( 14 )  'bc_pt_t_val                   '
219    WRITE ( 14 )  bc_pt_t_val
220    WRITE ( 14 )  'bc_q_b                        '
221    WRITE ( 14 )  bc_q_b
222    WRITE ( 14 )  'bc_q_t                        '
223    WRITE ( 14 )  bc_q_t
224    WRITE ( 14 )  'bc_q_t_val                    '
225    WRITE ( 14 )  bc_q_t_val
226    WRITE ( 14 )  'bc_s_b                        '
227    WRITE ( 14 )  bc_s_b
228    WRITE ( 14 )  'bc_s_t                        '
229    WRITE ( 14 )  bc_s_t
230    WRITE ( 14 )  'bc_sa_t                       '
231    WRITE ( 14 )  bc_sa_t
232    WRITE ( 14 )  'bc_uv_b                       '
233    WRITE ( 14 )  bc_uv_b
234    WRITE ( 14 )  'bc_uv_t                       '
235    WRITE ( 14 )  bc_uv_t
236    WRITE ( 14 )  'bottom_salinityflux           '
237    WRITE ( 14 )  bottom_salinityflux
238    WRITE ( 14 )  'building_height               '
239    WRITE ( 14 )  building_height
240    WRITE ( 14 )  'building_length_x             '
241    WRITE ( 14 )  building_length_x
242    WRITE ( 14 )  'building_length_y             '
243    WRITE ( 14 )  building_length_y
244    WRITE ( 14 )  'building_wall_left            '
245    WRITE ( 14 )  building_wall_left
246    WRITE ( 14 )  'building_wall_south           '
247    WRITE ( 14 )  building_wall_south
248    WRITE ( 14 )  'call_psolver_at_all_substeps  '
249    WRITE ( 14 )  call_psolver_at_all_substeps
250    WRITE ( 14 )  'canopy_mode                   '
251    WRITE ( 14 )  canopy_mode
252    WRITE ( 14 )  'canyon_height                 '
253    WRITE ( 14 )  canyon_height
254    WRITE ( 14 )  'canyon_width_x                '
255    WRITE ( 14 )  canyon_width_x
256    WRITE ( 14 )  'canyon_width_y                '
257    WRITE ( 14 )  canyon_width_y
258    WRITE ( 14 )  'canyon_wall_left              '
259    WRITE ( 14 )  canyon_wall_left
260    WRITE ( 14 )  'canyon_wall_south             '
261    WRITE ( 14 )  canyon_wall_south
262    WRITE ( 14 )  'c_sedimentation               '
263    WRITE ( 14 )  c_sedimentation
264    WRITE ( 14 )  'cfl_factor                    '
265    WRITE ( 14 )  cfl_factor
266    WRITE ( 14 )  'cloud_droplets                '
267    WRITE ( 14 )  cloud_droplets
268    WRITE ( 14 )  'cloud_physics                 '
269    WRITE ( 14 )  cloud_physics
270    WRITE ( 14 )  'cloud_scheme                  '
271    WRITE ( 14 )  cloud_scheme
272    WRITE ( 14 )  'collective_wait               '
273    WRITE ( 14 )  collective_wait
274    WRITE ( 14 )  'conserve_volume_flow          '
275    WRITE ( 14 )  conserve_volume_flow
276    WRITE ( 14 )  'conserve_volume_flow_mode     '
277    WRITE ( 14 )  conserve_volume_flow_mode
278    WRITE ( 14 )  'coupling_start_time           '
279    WRITE ( 14 )  coupling_start_time
280    WRITE ( 14 )  'current_timestep_number       '
281    WRITE ( 14 )  current_timestep_number
282    WRITE ( 14 )  'curvature_solution_effects    '
283    WRITE ( 14 )  curvature_solution_effects
284    WRITE ( 14 )  'cthf                          '
285    WRITE ( 14 )  cthf
286    WRITE ( 14 )  'cycle_mg                      '
287    WRITE ( 14 )  cycle_mg
288    WRITE ( 14 )  'damp_level_1d                 '
289    WRITE ( 14 )  damp_level_1d
290    WRITE ( 14 )  'dissipation_1d                '
291    WRITE ( 14 )  dissipation_1d
292    WRITE ( 14 )  'dp_external                   '
293    WRITE ( 14 )  dp_external
294    WRITE ( 14 )  'dp_level_b                    '
295    WRITE ( 14 )  dp_level_b
296    WRITE ( 14 )  'dp_smooth                     '
297    WRITE ( 14 )  dp_smooth
298    WRITE ( 14 )  'dpdxy                         '
299    WRITE ( 14 )  dpdxy
300    WRITE ( 14 )  'drag_coefficient              '
301    WRITE ( 14 )  drag_coefficient
302    WRITE ( 14 )  'drizzle                       '
303    WRITE ( 14 )  drizzle
304    WRITE ( 14 )  'dt_pr_1d                      '
305    WRITE ( 14 )  dt_pr_1d
306    WRITE ( 14 )  'dt_run_control_1d             '
307    WRITE ( 14 )  dt_run_control_1d
308    WRITE ( 14 )  'dt_3d                         '
309    WRITE ( 14 )  dt_3d
310    WRITE ( 14 )  'dvrp_filecount                '
311    WRITE ( 14 )  dvrp_filecount
312    WRITE ( 14 )  'dx                            '
313    WRITE ( 14 )  dx
314    WRITE ( 14 )  'dy                            '
315    WRITE ( 14 )  dy
316    WRITE ( 14 )  'dz                            '
317    WRITE ( 14 )  dz
318    WRITE ( 14 )  'dz_max                        '
319    WRITE ( 14 )  dz_max
320    WRITE ( 14 )  'dz_stretch_factor             '
321    WRITE ( 14 )  dz_stretch_factor
322    WRITE ( 14 )  'dz_stretch_level              '
323    WRITE ( 14 )  dz_stretch_level
324    WRITE ( 14 )  'e_min                         '
325    WRITE ( 14 )  e_min
326    WRITE ( 14 )  'end_time_1d                   '
327    WRITE ( 14 )  end_time_1d
328    WRITE ( 14 )  'fft_method                    '
329    WRITE ( 14 )  fft_method
330    WRITE ( 14 )  'first_call_lpm                '
331    WRITE ( 14 )  first_call_lpm
332    WRITE ( 14 )  'galilei_transformation        '
333    WRITE ( 14 )  galilei_transformation
334    WRITE ( 14 )  'hom                           '
335    WRITE ( 14 )  hom
336    WRITE ( 14 )  'hom_sum                       '
337    WRITE ( 14 )  hom_sum
338    WRITE ( 14 )  'humidity                      '
339    WRITE ( 14 )  humidity
340    IF ( ALLOCATED( inflow_damping_factor ) )  THEN
341       WRITE ( 14 )  'inflow_damping_factor         '
342       WRITE ( 14 )  inflow_damping_factor
343    ENDIF
344    WRITE ( 14 )  'inflow_damping_height         '
345    WRITE ( 14 )  inflow_damping_height
346    WRITE ( 14 )  'inflow_damping_width          '
347    WRITE ( 14 )  inflow_damping_width
348    WRITE ( 14 )  'inflow_disturbance_begin      '
349    WRITE ( 14 )  inflow_disturbance_begin
350    WRITE ( 14 )  'inflow_disturbance_end        '
351    WRITE ( 14 )  inflow_disturbance_end
352    WRITE ( 14 )  'km_constant                   '
353    WRITE ( 14 )  km_constant
354    WRITE ( 14 )  'lad                           '
355    WRITE ( 14 )  lad
356    WRITE ( 14 )  'lad_surface                   '
357    WRITE ( 14 )  lad_surface
358    WRITE ( 14 )  'lad_vertical_gradient         '
359    WRITE ( 14 )  lad_vertical_gradient
360    WRITE ( 14 )  'lad_vertical_gradient_level   '
361    WRITE ( 14 )  lad_vertical_gradient_level
362    WRITE ( 14 )  'lad_vertical_gradient_level_in'
363    WRITE ( 14 )  lad_vertical_gradient_level_ind
364    WRITE ( 14 )  'large_scale_subsidence        '
365    WRITE ( 14 )  large_scale_subsidence
366    WRITE ( 14 )  'leaf_surface_concentration    '
367    WRITE ( 14 )  leaf_surface_concentration
368    WRITE ( 14 )  'limiter_sedimentation         '
369    WRITE ( 14 )  limiter_sedimentation
370    WRITE ( 14 )  'loop_optimization             '
371    WRITE ( 14 )  loop_optimization
372    WRITE ( 14 )  'masking_method                '
373    WRITE ( 14 )  masking_method
374    IF ( ALLOCATED( mean_inflow_profiles ) )  THEN
375       WRITE ( 14 )  'mean_inflow_profiles          '
376       WRITE ( 14 )  mean_inflow_profiles
377    ENDIF
378    WRITE ( 14 )  'mg_cycles                     '
379    WRITE ( 14 )  mg_cycles
380    WRITE ( 14 )  'mg_switch_to_pe0_level        '
381    WRITE ( 14 )  mg_switch_to_pe0_level
382    WRITE ( 14 )  'mixing_length_1d              '
383    WRITE ( 14 )  mixing_length_1d
384    WRITE ( 14 )  'momentum_advec                '
385    WRITE ( 14 )  momentum_advec
386    WRITE ( 14 )  'nc_const                      '
387    WRITE ( 14 )  nc_const
388    WRITE ( 14 )  'netcdf_precision              '
389    WRITE ( 14 )  netcdf_precision
390    WRITE ( 14 )  'neutral                       '
391    WRITE ( 14 )  neutral
392    WRITE ( 14 )  'ngsrb                         '
393    WRITE ( 14 )  ngsrb
394    WRITE ( 14 )  'nsor                          '
395    WRITE ( 14 )  nsor
396    WRITE ( 14 )  'nsor_ini                      '
397    WRITE ( 14 )  nsor_ini
398    WRITE ( 14 )  'nx                            '
399    WRITE ( 14 )  nx
400    WRITE ( 14 )  'ny                            '
401    WRITE ( 14 )  ny
402    WRITE ( 14 )  'ocean                         '
403    WRITE ( 14 )  ocean
404    WRITE ( 14 )  'old_dt                        '
405    WRITE ( 14 )  old_dt
406    WRITE ( 14 )  'omega                         '
407    WRITE ( 14 )  omega
408    WRITE ( 14 )  'omega_sor                     '
409    WRITE ( 14 )  omega_sor
410    WRITE ( 14 )  'output_for_t0                 '
411    WRITE ( 14 )  output_for_t0
412    WRITE ( 14 )  'passive_scalar                '
413    WRITE ( 14 )  passive_scalar
414    WRITE ( 14 )  'pch_index                     '
415    WRITE ( 14 )  pch_index
416    WRITE ( 14 )  'phi                           '
417    WRITE ( 14 )  phi
418    WRITE ( 14 )  'plant_canopy                  '
419    WRITE ( 14 )  plant_canopy
420    WRITE ( 14 )  'prandtl_layer                 '
421    WRITE ( 14 )  prandtl_layer
422    WRITE ( 14 )  'prandtl_number                '
423    WRITE ( 14 )  prandtl_number
424    WRITE ( 14 )  'precipitation                 '
425    WRITE ( 14 )  precipitation
426    WRITE ( 14 )  'psolver                       '
427    WRITE ( 14 )  psolver
428    WRITE ( 14 )  'pt_damping_factor             '
429    WRITE ( 14 )  pt_damping_factor
430    WRITE ( 14 )  'pt_damping_width              '
431    WRITE ( 14 )  pt_damping_width
432    WRITE ( 14 )  'pt_init                       '
433    WRITE ( 14 )  pt_init
434    WRITE ( 14 )  'pt_reference                  '
435    WRITE ( 14 )  pt_reference
436    WRITE ( 14 )  'pt_surface                    '
437    WRITE ( 14 )  pt_surface
438    WRITE ( 14 )  'pt_surface_initial_change     '
439    WRITE ( 14 )  pt_surface_initial_change
440    WRITE ( 14 )  'pt_vertical_gradient          '
441    WRITE ( 14 )  pt_vertical_gradient
442    WRITE ( 14 )  'pt_vertical_gradient_level    '
443    WRITE ( 14 )  pt_vertical_gradient_level
444    WRITE ( 14 )  'pt_vertical_gradient_level_ind'
445    WRITE ( 14 )  pt_vertical_gradient_level_ind
446    WRITE ( 14 )  'q_init                        '
447    WRITE ( 14 )  q_init
448    WRITE ( 14 )  'q_surface                     '
449    WRITE ( 14 )  q_surface
450    WRITE ( 14 )  'q_surface_initial_change      '
451    WRITE ( 14 )  q_surface_initial_change
452    WRITE ( 14 )  'q_vertical_gradient           '
453    WRITE ( 14 )  q_vertical_gradient
454    WRITE ( 14 )  'q_vertical_gradient_level     '
455    WRITE ( 14 )  q_vertical_gradient_level
456    WRITE ( 14 )  'q_vertical_gradient_level_ind '
457    WRITE ( 14 )  q_vertical_gradient_level_ind
458    WRITE ( 14 )  'radiation                     '
459    WRITE ( 14 )  radiation
460    WRITE ( 14 )  'random_generator              '
461    WRITE ( 14 )  random_generator
462    WRITE ( 14 )  'random_heatflux               '
463    WRITE ( 14 )  random_heatflux
464    WRITE ( 14 )  'rayleigh_damping_factor       '
465    WRITE ( 14 )  rayleigh_damping_factor
466    WRITE ( 14 )  'rayleigh_damping_height       '
467    WRITE ( 14 )  rayleigh_damping_height
468    WRITE ( 14 )  'recycling_width               '
469    WRITE ( 14 )  recycling_width
470    WRITE ( 14 )  'reference_state               '
471    WRITE ( 14 )  reference_state
472    WRITE ( 14 )  'ref_state                     '
473    WRITE ( 14 )  ref_state
474    WRITE ( 14 )  'residual_limit                '
475    WRITE ( 14 )  residual_limit
476    WRITE ( 14 )  'rif_max                       '
477    WRITE ( 14 )  rif_max
478    WRITE ( 14 )  'rif_min                       '
479    WRITE ( 14 )  rif_min
480    WRITE ( 14 )  'roughness_length              '
481    WRITE ( 14 )  roughness_length
482    WRITE ( 14 )  'runnr                         '
483    WRITE ( 14 )  runnr
484    WRITE ( 14 )  'run_coupled                   '
485    WRITE ( 14 )  run_coupled
486    WRITE ( 14 )  'sa_init                       '
487    WRITE ( 14 )  sa_init
488    WRITE ( 14 )  'sa_surface                    '
489    WRITE ( 14 )  sa_surface
490    WRITE ( 14 )  'sa_vertical_gradient          '
491    WRITE ( 14 )  sa_vertical_gradient
492    WRITE ( 14 )  'sa_vertical_gradient_level    '
493    WRITE ( 14 )  sa_vertical_gradient_level
494    WRITE ( 14 )  'scalar_advec                  '
495    WRITE ( 14 )  scalar_advec
496    WRITE ( 14 )  'scalar_exchange_coefficient   '
497    WRITE ( 14 )  scalar_exchange_coefficient
498    WRITE ( 14 )  'simulated_time                '
499    WRITE ( 14 )  simulated_time
500    WRITE ( 14 )  'surface_heatflux              '
501    WRITE ( 14 )  surface_heatflux
502    WRITE ( 14 )  'surface_pressure              '
503    WRITE ( 14 )  surface_pressure
504    WRITE ( 14 )  'surface_scalarflux            '
505    WRITE ( 14 )  surface_scalarflux   
506    WRITE ( 14 )  'surface_waterflux             '
507    WRITE ( 14 )  surface_waterflux   
508    WRITE ( 14 )  's_surface                     '
509    WRITE ( 14 )  s_surface
510    WRITE ( 14 )  's_surface_initial_change      '
511    WRITE ( 14 )  s_surface_initial_change
512    WRITE ( 14 )  's_vertical_gradient           '
513    WRITE ( 14 )  s_vertical_gradient
514    WRITE ( 14 )  's_vertical_gradient_level     '
515    WRITE ( 14 )  s_vertical_gradient_level
516    WRITE ( 14 )  'time_coupling                 '
517    WRITE ( 14 )  time_coupling
518    WRITE ( 14 )  'time_disturb                  '
519    WRITE ( 14 )  time_disturb
520    WRITE ( 14 )  'time_domask                   '
521    WRITE ( 14 )  time_domask
522    WRITE ( 14 )  'time_dopr                     '
523    WRITE ( 14 )  time_dopr
524    WRITE ( 14 )  'time_dopr_av                  '
525    WRITE ( 14 )  time_dopr_av
526    WRITE ( 14 )  'time_dopr_listing             '
527    WRITE ( 14 )  time_dopr_listing
528    WRITE ( 14 )  'time_dopts                    '
529    WRITE ( 14 )  time_dopts
530    WRITE ( 14 )  'time_dosp                     '
531    WRITE ( 14 )  time_dosp
532    WRITE ( 14 )  'time_dots                     '
533    WRITE ( 14 )  time_dots
534    WRITE ( 14 )  'time_do2d_xy                  '
535    WRITE ( 14 )  time_do2d_xy
536    WRITE ( 14 )  'time_do2d_xz                  '
537    WRITE ( 14 )  time_do2d_xz
538    WRITE ( 14 )  'time_do2d_yz                  '
539    WRITE ( 14 )  time_do2d_yz
540    WRITE ( 14 )  'time_do3d                     '
541    WRITE ( 14 )  time_do3d
542    WRITE ( 14 )  'time_do_av                    '
543    WRITE ( 14 )  time_do_av
544    WRITE ( 14 )  'time_do_sla                   '
545    WRITE ( 14 )  time_do_sla
546    WRITE ( 14 )  'time_dvrp                     '
547    WRITE ( 14 )  time_dvrp
548    WRITE ( 14 )  'time_restart                  '
549    WRITE ( 14 )  time_restart
550    WRITE ( 14 )  'time_run_control              '
551    WRITE ( 14 )  time_run_control
552    WRITE ( 14 )  'time_since_reference_point    '
553    WRITE ( 14 )  time_since_reference_point
554    WRITE ( 14 )  'time_sort_particles           '
555    WRITE ( 14 )  time_sort_particles
556    WRITE ( 14 )  'timestep_scheme               '
557    WRITE ( 14 )  timestep_scheme
558    WRITE ( 14 )  'topography                    '
559    WRITE ( 14 )  topography
560    WRITE ( 14 )  'topography_grid_convention    '
561    WRITE ( 14 )  topography_grid_convention
562    WRITE ( 14 )  'top_heatflux                  '
563    WRITE ( 14 )  top_heatflux
564    WRITE ( 14 )  'top_momentumflux_u            '
565    WRITE ( 14 )  top_momentumflux_u
566    WRITE ( 14 )  'top_momentumflux_v            '
567    WRITE ( 14 )  top_momentumflux_v
568    WRITE ( 14 )  'top_salinityflux              '
569    WRITE ( 14 )  top_salinityflux
570    WRITE ( 14 )  'tsc                           '
571    WRITE ( 14 )  tsc
572    WRITE ( 14 )  'turbulence                    '
573    WRITE ( 14 )  turbulence
574    WRITE ( 14 )  'turbulent_inflow              '
575    WRITE ( 14 )  turbulent_inflow
576    WRITE ( 14 )  'u_bulk                        '
577    WRITE ( 14 )  u_bulk
578    WRITE ( 14 )  'u_init                        '
579    WRITE ( 14 )  u_init
580    WRITE ( 14 )  'u_max                         '
581    WRITE ( 14 )  u_max
582    WRITE ( 14 )  'u_max_ijk                     '
583    WRITE ( 14 )  u_max_ijk
584    WRITE ( 14 )  'ug                            '
585    WRITE ( 14 )  ug
586    WRITE ( 14 )  'ug_surface                    '
587    WRITE ( 14 )  ug_surface
588    WRITE ( 14 )  'ug_vertical_gradient          '
589    WRITE ( 14 )  ug_vertical_gradient
590    WRITE ( 14 )  'ug_vertical_gradient_level    '
591    WRITE ( 14 )  ug_vertical_gradient_level
592    WRITE ( 14 )  'ug_vertical_gradient_level_ind'
593    WRITE ( 14 )  ug_vertical_gradient_level_ind
594    WRITE ( 14 )  'use_surface_fluxes            '
595    WRITE ( 14 )  use_surface_fluxes
596    WRITE ( 14 )  'use_top_fluxes                '
597    WRITE ( 14 )  use_top_fluxes
598    WRITE ( 14 )  'use_ug_for_galilei_tr         '
599    WRITE ( 14 )  use_ug_for_galilei_tr
600    WRITE ( 14 )  'use_upstream_for_tke          '
601    WRITE ( 14 )  use_upstream_for_tke
602    WRITE ( 14 )  'v_bulk                        '
603    WRITE ( 14 )  v_bulk
604    WRITE ( 14 )  'v_init                        '
605    WRITE ( 14 )  v_init
606    WRITE ( 14 )  'v_max                         '
607    WRITE ( 14 )  v_max
608    WRITE ( 14 )  'v_max_ijk                     '
609    WRITE ( 14 )  v_max_ijk
610    WRITE ( 14 )  'ventilation_effect            '
611    WRITE ( 14 )  ventilation_effect
612    WRITE ( 14 )  'vg                            '
613    WRITE ( 14 )  vg
614    WRITE ( 14 )  'vg_surface                    '
615    WRITE ( 14 )  vg_surface
616    WRITE ( 14 )  'vg_vertical_gradient          '
617    WRITE ( 14 )  vg_vertical_gradient
618    WRITE ( 14 )  'vg_vertical_gradient_level    '
619    WRITE ( 14 )  vg_vertical_gradient_level
620    WRITE ( 14 )  'vg_vertical_gradient_level_ind'
621    WRITE ( 14 )  vg_vertical_gradient_level_ind
622    WRITE ( 14 )  'volume_flow_area              '
623    WRITE ( 14 )  volume_flow_area
624    WRITE ( 14 )  'volume_flow_initial           '
625    WRITE ( 14 )  volume_flow_initial
626    WRITE ( 14 )  'wall_adjustment               '
627    WRITE ( 14 )  wall_adjustment
628    WRITE ( 14 )  'subs_vertical_gradient        '
629    WRITE ( 14 )  subs_vertical_gradient
630    WRITE ( 14 )  'subs_vertical_gradient_level  '
631    WRITE ( 14 )  subs_vertical_gradient_level
632    WRITE ( 14 )  'subs_vertical_gradient_level_i'
633    WRITE ( 14 )  subs_vertical_gradient_level_i
634    WRITE ( 14 )  'w_max                         '
635    WRITE ( 14 )  w_max
636    WRITE ( 14 )  'w_max_ijk                     '
637    WRITE ( 14 )  w_max_ijk
638    WRITE ( 14 )  'z0h_factor                    '
639    WRITE ( 14 )  z0h_factor
640
641!
642!-- Set the end-of-file mark
643    WRITE ( 14 )  '*** end ***                   '
644
645
646 END SUBROUTINE write_var_list
Note: See TracBrowser for help on using the repository browser.