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

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

last commit documented

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