Ignore:
Timestamp:
Sep 7, 2010 3:17:00 PM (14 years ago)
Author:
weinreis
Message:
 
File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/advec_particles.f90

    r557 r559  
    37943794
    37953795    IMPLICIT NONE
    3796    
    3797     INTEGER :: rbs
    37983796
    37993797    CHARACTER (LEN=10) ::  particle_binary_version
     
    38163814    ENDIF
    38173815
    3818     DO rbs = 0, numprocs/binary_io_blocksize-1     
    3819        IF ( mod_numprocs_size == rbs ) THEN
    3820 !
    3821 !--       Write the version number of the binary format.
    3822 !--       Attention: After changes to the following output commands the version
    3823 !--       ---   number of the variable particle_binary_version must be changed!
     3816!
     3817!-- Write the version number of the binary format.
     3818!-- Attention: After changes to the following output commands the version
     3819!-- ---------  number of the variable particle_binary_version must be changed!
    38243820!--            Also, the version number and the list of arrays to be read in
    38253821!--            init_particles must be adjusted accordingly.
    3826           particle_binary_version = '3.0'
    3827           WRITE ( 90 )  particle_binary_version
    3828 
    3829 !
    3830 !--       Write some particle parameters, the size of the particle arrays
    3831 !--       as well as other dvrp-plot variables.
    3832           WRITE ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,              &
     3822    particle_binary_version = '3.0'
     3823    WRITE ( 90 )  particle_binary_version
     3824
     3825!
     3826!-- Write some particle parameters, the size of the particle arrays as well as
     3827!-- other dvrp-plot variables.
     3828    WRITE ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                    &
    38333829                  maximum_number_of_particles, maximum_number_of_tailpoints,   &
    38343830                  maximum_number_of_tails, number_of_initial_particles,        &
     
    38373833                  time_write_particle_data, uniform_particles
    38383834
    3839           IF ( number_of_initial_particles /= 0 )    &
    3840              WRITE ( 90 )  initial_particles
    3841 
    3842           WRITE ( 90 )  prt_count, prt_start_index
    3843           WRITE ( 90 )  particles
    3844 
    3845           IF ( use_particle_tails )  THEN
    3846              WRITE ( 90 )  particle_tail_coordinates
    3847           ENDIF
    3848          
    3849        ENDIF 
    3850        CALL MPI_BARRIER(comm2d, ierr )   
    3851     ENDDO
     3835    IF ( number_of_initial_particles /= 0 )  WRITE ( 90 )  initial_particles
     3836
     3837    WRITE ( 90 )  prt_count, prt_start_index
     3838    WRITE ( 90 )  particles
     3839
     3840    IF ( use_particle_tails )  THEN
     3841       WRITE ( 90 )  particle_tail_coordinates
     3842    ENDIF
    38523843
    38533844    CLOSE ( 90 )
Note: See TracChangeset for help on using the changeset viewer.