source: palm/tags/release-3.7/SOURCE/write_3d_binary.f90 @ 3806

Last change on this file since 3806 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: 10.7 KB
Line 
1 SUBROUTINE write_3d_binary
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: write_3d_binary.f90 392 2009-09-24 10:39:14Z raasch $
11!
12! 367 2009-08-25 08:35:52Z maronga
13! +shf_av, qsws_av
14!
15! 145 2008-01-09 08:17:38Z raasch
16! write_var_list is only called for pe0, -dopr_time_count,
17! hom_sum moved, volume_flow_area, volume_flow_initial moved to write_var_list,
18! writing of old profil parameters (cross_..., dopr_crossindex, profile_***)
19! removed
20!
21! 102 2007-07-27 09:09:17Z raasch
22! +uswst, uswst_m, vswst, vswst_m
23!
24! 96 2007-06-04 08:07:41Z raasch
25! +rho_av, sa, sa_av, saswsb, saswst
26!
27! 75 2007-03-22 09:54:05Z raasch
28! +precipitation_amount, precipitation_rate_av, rif_wall, u_m_l, u_m_r, etc.,
29! z0_av, moisture renamed humidity
30!
31! 19 2007-02-23 04:53:48Z raasch
32! +qswst, qswst_m, tswst, tswst_m
33!
34! RCS Log replace by Id keyword, revision history cleaned up
35!
36! Revision 1.21  2006/08/04 15:05:11  raasch
37! +iran, iran_part
38!
39! Revision 1.1  1998/03/18 20:20:21  raasch
40! Initial revision
41!
42!
43! Description:
44! ------------
45! Binary output of variables and arrays for restarts.
46!------------------------------------------------------------------------------!
47
48    USE arrays_3d
49    USE averaging
50    USE cloud_parameters
51    USE control_parameters
52    USE cpulog
53    USE indices
54    USE interfaces
55    USE particle_attributes
56    USE pegrid
57    USE profil_parameter
58    USE random_function_mod
59    USE statistics
60
61    IMPLICIT NONE
62
63    CHARACTER (LEN=10) ::  binary_version
64
65
66    CALL cpu_log( log_point(22), 'write_3d_binary', 'start' )
67
68    CALL check_open( 14 )
69   
70!
71!-- Write control parameters and other variables for restart.
72    IF ( myid == 0 )  CALL write_var_list
73
74!
75!-- Write arrays.
76    binary_version = '3.1'
77
78    WRITE ( 14 )  binary_version
79
80    WRITE ( 14 )  numprocs, myid, nxl, nxr, nys, nyn, nzb, nzt
81
82!
83!-- Attention: After changes to the following output commands the version number
84!-- ---------  of the variable binary_version must be changed!
85!--            Also, the list of arrays to be read in read_3d_binary must be
86!--            adjusted accordingly.
87
88    WRITE ( 14 )  'e                   ';  WRITE ( 14 )  e
89    IF ( ALLOCATED( e_av ) )  THEN
90       WRITE ( 14 )  'e_av                ';  WRITE ( 14 )  e_av
91    ENDIF
92    WRITE ( 14 )  'e_m                 ';  WRITE ( 14 )  e_m
93    WRITE ( 14 )  'iran                ';  WRITE ( 14 )  iran, iran_part
94    WRITE ( 14 )  'kh                  ';  WRITE ( 14 )  kh
95    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
96       WRITE ( 14 )  'kh_m                ';  WRITE ( 14 )  kh_m
97    ENDIF
98    WRITE ( 14 )  'km                  ';  WRITE ( 14 )  km
99    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
100       WRITE ( 14 )  'km_m                ';  WRITE ( 14 )  km_m
101    ENDIF
102    IF ( ALLOCATED( lwp_av ) )  THEN
103       WRITE ( 14 )  'lwp_av              ';  WRITE ( 14 )  lwp_av
104    ENDIF
105    WRITE ( 14 )  'p                   ';  WRITE ( 14 )  p
106    IF ( ALLOCATED( p_av ) )  THEN
107       WRITE ( 14 )  'p_av                ';  WRITE ( 14 )  p_av
108    ENDIF
109    IF ( ALLOCATED( pc_av ) )  THEN
110       WRITE ( 14 )  'pc_av               ';  WRITE ( 14 )  pc_av
111    ENDIF
112    IF ( ALLOCATED( pr_av ) )  THEN
113       WRITE ( 14 )  'pr_av               ';  WRITE ( 14 )  pr_av
114    ENDIF
115    IF ( ALLOCATED( precipitation_amount ) )  THEN
116       WRITE ( 14 )  'precipitation_amount';  WRITE ( 14 )  precipitation_amount
117    ENDIF
118    IF ( ALLOCATED( precipitation_rate_av ) )  THEN
119       WRITE ( 14 )  'precipitation_rate_a';  WRITE ( 14 )  &
120                                                           precipitation_rate_av
121    ENDIF
122    WRITE ( 14 )  'pt                  ';  WRITE ( 14 )  pt
123    IF ( ALLOCATED( pt_av ) )  THEN
124       WRITE ( 14 )  'pt_av               ';  WRITE ( 14 )  pt_av
125    ENDIF
126    WRITE ( 14 )  'pt_m                ';  WRITE ( 14 )  pt_m
127    IF ( humidity  .OR. passive_scalar )  THEN
128       WRITE ( 14 )  'q                   ';  WRITE ( 14 )  q 
129       IF ( ALLOCATED( q_av ) )  THEN
130          WRITE ( 14 )  'q_av                ';  WRITE ( 14 )  q_av
131       ENDIF
132       WRITE ( 14 )  'q_m                 ';  WRITE ( 14 ) q_m
133       IF ( cloud_physics ) THEN
134          WRITE ( 14 )  'ql                  ';  WRITE ( 14 ) ql
135          IF ( ALLOCATED( ql_av ) )  THEN
136             WRITE ( 14 )  'ql_av               ';  WRITE ( 14 )  ql_av
137          ENDIF
138       ENDIF
139       WRITE ( 14 )  'qs                  ';  WRITE ( 14 ) qs
140       WRITE ( 14 )  'qsws                ';  WRITE ( 14 ) qsws
141       IF ( timestep_scheme(1:5) /= 'runge' )  THEN
142          WRITE ( 14 )  'qsws_m              ';  WRITE ( 14 ) qsws_m
143       ENDIF
144       IF ( ALLOCATED( qsws_av ) )  THEN
145          WRITE ( 14 )  'qsws_av             ';  WRITE ( 14 )  qsws_av
146       ENDIF
147       WRITE ( 14 )  'qswst               ';  WRITE ( 14 ) qswst
148       IF ( timestep_scheme(1:5) /= 'runge' )  THEN
149          WRITE ( 14 )  'qswst_m             ';  WRITE ( 14 ) qswst_m
150       ENDIF
151    ENDIF
152    IF ( ocean )  THEN
153       IF ( ALLOCATED( rho_av ) )  THEN
154          WRITE ( 14 )  'rho_av              ';  WRITE ( 14 )  rho_av
155       ENDIF
156       WRITE ( 14 )  'sa                  ';  WRITE ( 14 )  sa
157       IF ( ALLOCATED( sa_av ) )  THEN
158          WRITE ( 14 )  'sa_av               ';  WRITE ( 14 )  sa_av
159       ENDIF
160       WRITE ( 14 )  'saswsb              ';  WRITE ( 14 )  saswsb
161       WRITE ( 14 )  'saswst              ';  WRITE ( 14 )  saswst
162    ENDIF
163    IF ( ALLOCATED( ql_c_av ) )  THEN
164       WRITE ( 14 )  'ql_c_av             ';  WRITE ( 14 )  ql_c_av
165    ENDIF
166    IF ( ALLOCATED( ql_v_av ) )  THEN
167       WRITE ( 14 )  'ql_v_av             ';  WRITE ( 14 )  ql_v_av
168    ENDIF
169    IF ( ALLOCATED( ql_vp_av ) )  THEN
170       WRITE ( 14 )  'ql_vp_av            ';  WRITE ( 14 )  ql_vp_av
171    ENDIF
172    IF ( ALLOCATED( qv_av ) )  THEN
173       WRITE ( 14 )  'qv_av               ';  WRITE ( 14 )  qv_av
174    ENDIF
175    WRITE ( 14 )  'random_iv           ';  WRITE ( 14 )  random_iv
176                                           WRITE ( 14 )  random_iy
177    WRITE ( 14 )  'rif                 ';  WRITE ( 14 )  rif
178    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
179       WRITE ( 14 )  'rif_m               ';  WRITE ( 14 )  rif_m
180    ENDIF
181    IF ( topography /= 'flat' )  THEN
182       WRITE ( 14 )  'rif_wall            ';  WRITE ( 14 )  rif_wall
183    ENDIF
184    IF ( ALLOCATED( s_av ) )  THEN
185       WRITE ( 14 )  's_av                ';  WRITE ( 14 )  s_av
186    ENDIF
187    WRITE ( 14 )  'shf                 ';  WRITE ( 14 )  shf
188    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
189       WRITE ( 14 )  'shf_m               ';  WRITE ( 14 )  shf_m
190    ENDIF
191    IF ( ALLOCATED( shf_av ) )  THEN
192       WRITE ( 14 )  'shf_av              ';  WRITE ( 14 )  shf_av
193    ENDIF
194    IF ( ALLOCATED( spectrum_x ) )  THEN
195       WRITE ( 14 )  'spectrum_x          ';  WRITE ( 14 )  spectrum_x
196       WRITE ( 14 )  'spectrum_y          ';  WRITE ( 14 )  spectrum_y
197    ENDIF
198    WRITE ( 14 )  'ts                  ';  WRITE ( 14 )  ts
199    IF ( ALLOCATED( ts_av ) )  THEN
200       WRITE ( 14 )  'ts_av               ';  WRITE ( 14 )  ts_av
201    ENDIF
202    WRITE ( 14 )  'tswst               ';  WRITE ( 14 )  tswst
203    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
204       WRITE ( 14 )  'tswst_m             ';  WRITE ( 14 )  tswst_m
205    ENDIF
206    WRITE ( 14 )  'u                   ';  WRITE ( 14 )  u
207    IF ( ALLOCATED( u_av ) )  THEN
208       WRITE ( 14 )  'u_av                ';  WRITE ( 14 )  u_av
209    ENDIF
210    WRITE ( 14 )  'u_m                 ';  WRITE ( 14 )  u_m
211    IF ( ALLOCATED( u_m_l ) )  THEN
212       WRITE ( 14 )  'u_m_l               ';  WRITE ( 14 )  u_m_l
213    ENDIF
214    IF ( ALLOCATED( u_m_n ) )  THEN
215       WRITE ( 14 )  'u_m_n               ';  WRITE ( 14 )  u_m_n
216    ENDIF
217    IF ( ALLOCATED( u_m_r ) )  THEN
218       WRITE ( 14 )  'u_m_r               ';  WRITE ( 14 )  u_m_r
219    ENDIF
220    IF ( ALLOCATED( u_m_s ) )  THEN
221       WRITE ( 14 )  'u_m_s               ';  WRITE ( 14 )  u_m_s
222    ENDIF
223    WRITE ( 14 )  'us                  ';  WRITE ( 14 )  us
224    WRITE ( 14 )  'usws                ';  WRITE ( 14 )  usws
225    WRITE ( 14 )  'uswst               ';  WRITE ( 14 )  uswst
226    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
227       WRITE ( 14 )  'usws_m              ';  WRITE ( 14 )  usws_m
228       WRITE ( 14 )  'uswst_m             ';  WRITE ( 14 )  uswst_m
229    ENDIF
230    IF ( ALLOCATED( us_av ) )  THEN
231       WRITE ( 14 )  'us_av               ';  WRITE ( 14 )  us_av
232    ENDIF
233    WRITE ( 14 )  'v                   ';  WRITE ( 14 )  v
234    IF ( ALLOCATED( v_av ) )  THEN
235       WRITE ( 14 )  'v_av                ';  WRITE ( 14 )  v_av
236    ENDIF
237    WRITE ( 14 )  'v_m                 ';  WRITE ( 14 )  v_m
238    IF ( ALLOCATED( v_m_l ) )  THEN
239       WRITE ( 14 )  'v_m_l               ';  WRITE ( 14 )  v_m_l
240    ENDIF
241    IF ( ALLOCATED( v_m_n ) )  THEN
242       WRITE ( 14 )  'v_m_n               ';  WRITE ( 14 )  v_m_n
243    ENDIF
244    IF ( ALLOCATED( v_m_r ) )  THEN
245       WRITE ( 14 )  'v_m_r               ';  WRITE ( 14 )  v_m_r
246    ENDIF
247    IF ( ALLOCATED( v_m_s ) )  THEN
248       WRITE ( 14 )  'v_m_s               ';  WRITE ( 14 )  v_m_s
249    ENDIF
250    IF ( humidity )  THEN
251       WRITE ( 14 )  'vpt                 ';  WRITE ( 14 )  vpt
252       IF ( ALLOCATED( vpt_av ) )  THEN
253          WRITE ( 14 )  'vpt_av              ';  WRITE ( 14 )  vpt_av
254       ENDIF
255       IF ( timestep_scheme(1:5) /= 'runge' )  THEN
256          WRITE ( 14 )  'vpt_m               ';  WRITE ( 14 )  vpt_m
257       ENDIF
258    ENDIF
259    WRITE ( 14 )  'vsws                ';  WRITE ( 14 )  vsws
260    WRITE ( 14 )  'vswst               ';  WRITE ( 14 )  vswst
261    IF ( timestep_scheme(1:5) /= 'runge' )  THEN
262       WRITE ( 14 )  'vsws_m              ';  WRITE ( 14 )  vsws_m
263       WRITE ( 14 )  'vswst_m             ';  WRITE ( 14 )  vswst_m
264    ENDIF
265    WRITE ( 14 )  'w                   ';  WRITE ( 14 )  w
266    IF ( ALLOCATED( w_av ) )  THEN
267       WRITE ( 14 )  'w_av                ';  WRITE ( 14 )  w_av
268    ENDIF
269    WRITE ( 14 )  'w_m                 ';  WRITE ( 14 )  w_m
270    IF ( ALLOCATED( w_m_l ) )  THEN
271       WRITE ( 14 )  'w_m_l               ';  WRITE ( 14 )  w_m_l
272    ENDIF
273    IF ( ALLOCATED( w_m_n ) )  THEN
274       WRITE ( 14 )  'w_m_n               ';  WRITE ( 14 )  w_m_n
275    ENDIF
276    IF ( ALLOCATED( w_m_r ) )  THEN
277       WRITE ( 14 )  'w_m_r               ';  WRITE ( 14 )  w_m_r
278    ENDIF
279    IF ( ALLOCATED( w_m_s ) )  THEN
280       WRITE ( 14 )  'w_m_s               ';  WRITE ( 14 )  w_m_s
281    ENDIF
282    WRITE ( 14 )  'z0                  ';  WRITE ( 14 )  z0
283    IF ( ALLOCATED( z0_av ) )  THEN
284       WRITE ( 14 )  'z0_av               ';  WRITE ( 14 )  z0_av
285    ENDIF
286
287!
288!-- Write end label. Unit 14 is closed in the main program.
289    WRITE ( 14 )  '*** end ***         '
290
291
292    CALL cpu_log( log_point(22), 'write_3d_binary', 'stop' )
293
294
295 END SUBROUTINE write_3d_binary
Note: See TracBrowser for help on using the repository browser.