Ignore:
Timestamp:
Mar 15, 2012 10:35:09 AM (12 years ago)
Author:
raasch
Message:

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

File:
1 moved

Legend:

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

    r848 r849  
    1  SUBROUTINE init_particles
     1 SUBROUTINE lpm_init
    22
    33!------------------------------------------------------------------------------!
    44! Current revisions:
    55! -----------------
    6 !
     6! routine renamed: init_particles -> lpm_init
     7! de_dx, de_dy, de_dz are allocated here (instead of automatic arrays in
     8! advec_particles),
     9! sort_particles renamed lpm_sort_arrays, user_init_particles renamed lpm_init
    710!
    811! Former revisions:
     
    6568! ------------
    6669! This routine initializes a set of particles and their attributes (position,
    67 ! radius, ..). Advection of these particles is carried out by advec_particles,
    68 ! plotting is done in data_output_dvrp.
     70! radius, ..) which are used by the Lagrangian particle model (see lpm).
    6971!------------------------------------------------------------------------------!
    7072
     
    8385    IMPLICIT NONE
    8486
    85     CHARACTER (LEN=10) ::  particle_binary_version, version_on_file
    86 
    8787    INTEGER ::  i, j, n, nn
    8888#if defined( __parallel )
     
    124124                                  '&number_of_particle_groups reset to ', &
    125125                                  max_number_of_particle_groups
    126        CALL message( 'init_particles', 'PA0213', 0, 1, 0, 6, 0 )
     126       CALL message( 'lpm_init', 'PA0213', 0, 1, 0, 6, 0 )
    127127       number_of_particle_groups = max_number_of_particle_groups
    128128    ENDIF
     
    154154
    155155!
     156!-- Allocate arrays required for calculating particle SGS velocities
     157    IF ( use_sgs_for_particles )  THEN
     158       ALLOCATE( de_dx(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
     159                 de_dy(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
     160                 de_dz(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     161    ENDIF
     162
     163!
    156164!-- Initialize collision kernels
    157165    IF ( collision_kernel /= 'none' )  CALL init_kernels
     
    159167!
    160168!-- For the first model run of a possible job chain initialize the
    161 !-- particles, otherwise read the particle data from file.
     169!-- particles, otherwise read the particle data from restart file.
    162170    IF ( TRIM( initializing_actions ) == 'read_restart_data'  &
    163171         .AND.  read_particles_from_restartfile )  THEN
    164172
    165 !
    166 !--    Read particle data from previous model run.
    167 !--    First open the input unit.
    168        IF ( myid_char == '' )  THEN
    169           OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN'//myid_char, &
    170                      FORM='UNFORMATTED' )
    171        ELSE
    172           OPEN ( 90, FILE='PARTICLE_RESTART_DATA_IN/'//myid_char, &
    173                      FORM='UNFORMATTED' )
    174        ENDIF
    175 
    176 !
    177 !--    First compare the version numbers
    178        READ ( 90 )  version_on_file
    179        particle_binary_version = '3.0'
    180        IF ( TRIM( version_on_file ) /= TRIM( particle_binary_version ) )  THEN
    181           message_string = 'version mismatch concerning data from prior ' // &
    182                            'run &version on file    = "' //                  &
    183                                          TRIM( version_on_file ) //          &
    184                            '&version in program = "' //                      &
    185                                          TRIM( particle_binary_version ) // '"'
    186           CALL message( 'init_particles', 'PA0214', 1, 2, 0, 6, 0 )
    187        ENDIF
    188 
    189 !
    190 !--    Read some particle parameters and the size of the particle arrays,
    191 !--    allocate them and read their contents.
    192        READ ( 90 )  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,                  &
    193                     maximum_number_of_particles, maximum_number_of_tailpoints, &
    194                     maximum_number_of_tails, number_of_initial_particles,      &
    195                     number_of_particles, number_of_particle_groups,            &
    196                     number_of_tails, particle_groups, time_prel,               &
    197                     time_write_particle_data, uniform_particles
    198 
    199        IF ( number_of_initial_particles /= 0 )  THEN
    200           ALLOCATE( initial_particles(1:number_of_initial_particles) )
    201           READ ( 90 )  initial_particles
    202        ENDIF
    203 
    204        ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
    205                  prt_start_index(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
    206                  particle_mask(maximum_number_of_particles),     &
    207                  part_1(maximum_number_of_particles),            &
    208                  part_2(maximum_number_of_particles) )
    209 
    210        part_1 = particle_type( 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
    211                                0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
    212                                0.0, 0, 0, 0, 0 )
    213 
    214        part_2 = particle_type( 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
    215                                0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
    216                                0.0, 0, 0, 0, 0 )
    217 
    218        sort_count = 0
    219 
    220        particles => part_1
    221 
    222        READ ( 90 )  prt_count, prt_start_index
    223        READ ( 90 )  particles
    224 
    225        IF ( use_particle_tails )  THEN
    226           ALLOCATE( particle_tail_coordinates(maximum_number_of_tailpoints,5, &
    227                     maximum_number_of_tails),                                 &
    228                     new_tail_id(maximum_number_of_tails),                     &
    229                     tail_mask(maximum_number_of_tails) )
    230           READ ( 90 )  particle_tail_coordinates
    231        ENDIF
    232 
    233        CLOSE ( 90 )
     173       CALL lpm_read_restart_file
    234174
    235175    ELSE
     
    278218             WRITE( message_string, * ) 'particle group #', i, 'has a', &
    279219                                        'density ratio /= 0 but radius = 0'
    280              CALL message( 'init_particles', 'PA0215', 1, 2, 0, 6, 0 )
     220             CALL message( 'lpm_init', 'PA0215', 1, 2, 0, 6, 0 )
    281221          ENDIF
    282222          particle_groups(i)%density_ratio = density_ratio(i)
     
    318258                                      maximum_number_of_particles, ') on PE ', &
    319259                                             myid
    320                                CALL message( 'init_particles', 'PA0216', &
    321                                                                  2, 2, -1, 6, 1 )
     260                               CALL message( 'lpm_init', 'PA0216', 2, 2, -1, 6,&
     261                                             1 )
    322262                            ENDIF
    323263                            particles(n)%x             = pos_x
     
    410350!
    411351!--    User modification of initial particles
    412        CALL user_init_particles
     352       CALL user_lpm_init
    413353
    414354!
     
    456396!--    Sort particles in the sequence the gridboxes are stored in the memory.
    457397!--    Only required if cloud droplets are used.
    458        IF ( cloud_droplets )  CALL sort_particles
     398       IF ( cloud_droplets )  CALL lpm_sort_arrays
    459399
    460400!
     
    575515          WRITE( message_string, * )  'unknown boundary condition ',   &
    576516                                       'bc_par_b = "', TRIM( bc_par_b ), '"'
    577           CALL message( 'init_particles', 'PA0217', 1, 2, 0, 6, 0 )
     517          CALL message( 'lpm_init', 'PA0217', 1, 2, 0, 6, 0 )
    578518         
    579519    END SELECT
     
    589529          WRITE( message_string, * ) 'unknown boundary condition ',   &
    590530                                     'bc_par_t = "', TRIM( bc_par_t ), '"'
    591           CALL message( 'init_particles', 'PA0218', 1, 2, 0, 6, 0 )
     531          CALL message( 'lpm_init', 'PA0218', 1, 2, 0, 6, 0 )
    592532         
    593533    END SELECT
     
    606546          WRITE( message_string, * ) 'unknown boundary condition ',   &
    607547                                     'bc_par_lr = "', TRIM( bc_par_lr ), '"'
    608           CALL message( 'init_particles', 'PA0219', 1, 2, 0, 6, 0 )
     548          CALL message( 'lpm_init', 'PA0219', 1, 2, 0, 6, 0 )
    609549         
    610550    END SELECT
     
    623563          WRITE( message_string, * ) 'unknown boundary condition ',   &
    624564                                     'bc_par_ns = "', TRIM( bc_par_ns ), '"'
    625           CALL message( 'init_particles', 'PA0220', 1, 2, 0, 6, 0 )
     565          CALL message( 'lpm_init', 'PA0220', 1, 2, 0, 6, 0 )
    626566         
    627567    END SELECT
     
    6305708000 FORMAT (I6,1X,F7.2,4X,I6,71X,I6)
    631571
    632  END SUBROUTINE init_particles
     572 END SUBROUTINE lpm_init
Note: See TracChangeset for help on using the changeset viewer.