source: palm/trunk/SOURCE/lpm_write_restart_file.f90 @ 849

Last change on this file since 849 was 849, checked in by raasch, 12 years ago

Changed:


Original routine advec_particles split into several new subroutines and renamed
lpm.
init_particles renamed lpm_init
user_advec_particles renamed user_lpm_advec,
particle_boundary_conds renamed lpm_boundary_conds,
set_particle_attributes renamed lpm_set_attributes,
user_init_particles renamed user_lpm_init,
user_particle_attributes renamed user_lpm_set_attributes
(Makefile, lpm_droplet_collision, lpm_droplet_condensation, init_3d_model, modules, palm, read_var_list, time_integration, write_var_list, deleted: advec_particles, init_particles, particle_boundary_conds, set_particle_attributes, user_advec_particles, user_init_particles, user_particle_attributes, new: lpm, lpm_advec, lpm_boundary_conds, lpm_calc_liquid_water_content, lpm_data_output_particles, lpm_droplet_collision, lpm_drollet_condensation, lpm_exchange_horiz, lpm_extend_particle_array, lpm_extend_tails, lpm_extend_tail_array, lpm_init, lpm_init_sgs_tke, lpm_pack_arrays, lpm_read_restart_file, lpm_release_set, lpm_set_attributes, lpm_sort_arrays, lpm_write_exchange_statistics, lpm_write_restart_file, user_lpm_advec, user_lpm_init, user_lpm_set_attributes

  • Property svn:keywords set to Id
File size: 2.7 KB
Line 
1 SUBROUTINE lpm_write_restart_file
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! ------------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: lpm_write_restart_file.f90 849 2012-03-15 10:35:09Z raasch $
11!
12!
13! Description:
14! ------------
15! Write particle data in FORTRAN binary format on restart file
16!------------------------------------------------------------------------------!
17
18    USE control_parameters
19    USE particle_attributes
20    USE pegrid
21
22    IMPLICIT NONE
23
24    CHARACTER (LEN=10) ::  particle_binary_version
25    INTEGER ::  i
26
27!
28!-- First open the output unit.
29    IF ( myid_char == '' )  THEN
30       OPEN ( 90, FILE='PARTICLE_RESTART_DATA_OUT'//myid_char, &
31                  FORM='UNFORMATTED')
32    ELSE
33       IF ( myid == 0 )  CALL local_system( 'mkdir PARTICLE_RESTART_DATA_OUT' )
34#if defined( __parallel )
35!
36!--    Set a barrier in order to allow that thereafter all other processors
37!--    in the directory created by PE0 can open their file
38       CALL MPI_BARRIER( comm2d, ierr )
39#endif
40       OPEN ( 90, FILE='PARTICLE_RESTART_DATA_OUT/'//myid_char, &
41                  FORM='UNFORMATTED' )
42    ENDIF
43
44    DO  i = 0, io_blocks-1
45
46       IF ( i == io_group )  THEN
47
48!
49!--       Write the version number of the binary format.
50!--       Attention: After changes to the following output commands the version
51!--       ---------  number of the variable particle_binary_version must be
52!--                  changed! Also, the version number and the list of arrays
53!--                  to be read in lpm_read_restart_file must be adjusted
54!--                  accordingly.
55          particle_binary_version = '3.0'
56          WRITE ( 90 )  particle_binary_version
57
58!
59!--       Write some particle parameters, the size of the particle arrays as
60!--       well as other dvrp-plot variables.
61          WRITE ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,              &
62                        maximum_number_of_particles,                           &
63                        maximum_number_of_tailpoints, maximum_number_of_tails, &
64                        number_of_initial_particles, number_of_particles,      &
65                        number_of_particle_groups, number_of_tails,            &
66                        particle_groups, time_prel, time_write_particle_data,  &
67                        uniform_particles
68
69          IF ( number_of_initial_particles /= 0 ) WRITE ( 90 ) initial_particles
70
71          WRITE ( 90 )  prt_count, prt_start_index
72          WRITE ( 90 )  particles
73
74          IF ( use_particle_tails )  THEN
75             WRITE ( 90 )  particle_tail_coordinates
76          ENDIF
77
78          CLOSE ( 90 )
79
80       ENDIF
81
82#if defined( __parallel )
83       CALL MPI_BARRIER( comm2d, ierr )
84#endif
85
86    ENDDO
87
88
89 END SUBROUTINE lpm_write_restart_file
Note: See TracBrowser for help on using the repository browser.