Ignore:
Timestamp:
Apr 7, 2016 7:49:42 AM (8 years ago)
Author:
hoffmann
Message:

changes in LPM and bulk cloud microphysics

File:
1 edited

Legend:

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

    r1818 r1822  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Tails removed. Unused variables removed.
    2222!
    2323! Former revisions:
     
    5050!------------------------------------------------------------------------------!
    5151 SUBROUTINE lpm_write_restart_file
    52  
    5352
    54     USE control_parameters,                                                    &
    55         ONLY:  io_blocks, io_group
    5653
    5754    USE indices,                                                               &
     
    6259    USE particle_attributes,                                                   &
    6360        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, grid_particles,       &
    64                maximum_number_of_tails, maximum_number_of_tailpoints,          &
    6561               number_of_particles, number_of_particle_groups,                 &
    66                number_of_tails, particles, particle_groups,                    &
    67                particle_tail_coordinates, prt_count, time_prel,                &
    68                time_write_particle_data, uniform_particles,                    &
    69                use_particle_tails, zero_particle
     62               particles, particle_groups, prt_count, time_prel,               &
     63               time_write_particle_data, uniform_particles
    7064
    7165    USE pegrid
     
    7569    CHARACTER (LEN=10) ::  particle_binary_version   !<
    7670
    77     INTEGER(iwp) ::  i                               !<
    7871    INTEGER(iwp) ::  ip                              !<
    7972    INTEGER(iwp) ::  jp                              !<
     
    9790    ENDIF
    9891
    99 !    DO  i = 0, io_blocks-1
    100 
    101 !       IF ( i == io_group )  THEN
     92!
     93!-- Write the version number of the binary format.
     94!-- Attention: After changes to the following output commands the version
     95!-- ---------  number of the variable particle_binary_version must be
     96!--            changed! Also, the version number and the list of arrays
     97!--            to be read in lpm_read_restart_file must be adjusted
     98!--            accordingly.
     99    particle_binary_version = '4.0'
     100    WRITE ( 90 )  particle_binary_version
    102101
    103102!
    104 !--       Write the version number of the binary format.
    105 !--       Attention: After changes to the following output commands the version
    106 !--       ---------  number of the variable particle_binary_version must be
    107 !--                  changed! Also, the version number and the list of arrays
    108 !--                  to be read in lpm_read_restart_file must be adjusted
    109 !--                  accordingly.
    110           particle_binary_version = '3.2'
    111           WRITE ( 90 )  particle_binary_version
     103!-- Write some particle parameters, the size of the particle arrays as
     104!-- well as other dvrp-plot variables.
     105    WRITE ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,              &
     106                  number_of_particle_groups, particle_groups, time_prel, &
     107                  time_write_particle_data, uniform_particles
    112108
    113 !
    114 !--       Write some particle parameters, the size of the particle arrays as
    115 !--       well as other dvrp-plot variables.
    116           WRITE ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,              &
    117                         maximum_number_of_tailpoints, maximum_number_of_tails, &
    118                         number_of_particle_groups, number_of_tails,            &
    119                         particle_groups, time_prel, time_write_particle_data,  &
    120                         uniform_particles
     109    WRITE ( 90 )  prt_count
     110         
     111    DO  ip = nxl, nxr
     112       DO  jp = nys, nyn
     113          DO  kp = nzb+1, nzt
     114             number_of_particles = prt_count(kp,jp,ip)
     115             particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
     116             IF ( number_of_particles <= 0 )  CYCLE
     117             WRITE ( 90 )  particles
     118          ENDDO
     119       ENDDO
     120    ENDDO
    121121
    122           WRITE ( 90 )  prt_count
    123          
    124           DO  ip = nxl, nxr
    125              DO  jp = nys, nyn
    126                 DO  kp = nzb+1, nzt
    127                    number_of_particles = prt_count(kp,jp,ip)
    128                    particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
    129                    IF ( number_of_particles <= 0 )  CYCLE
    130                    WRITE ( 90 )  particles
    131                 ENDDO
    132              ENDDO
    133           ENDDO
    134 
    135 !
    136 !--       particle tails currently not available
    137 !          IF ( use_particle_tails )  THEN
    138 !             WRITE ( 90 )  particle_tail_coordinates
    139 !          ENDIF
    140 
    141           CLOSE ( 90 )
    142 
    143 !       ENDIF
     122    CLOSE ( 90 )
    144123
    145124#if defined( __parallel )
     
    147126#endif
    148127
    149  !   ENDDO
    150 
    151128
    152129 END SUBROUTINE lpm_write_restart_file
Note: See TracChangeset for help on using the changeset viewer.