Changeset 1936


Ignore:
Timestamp:
Jun 13, 2016 1:37:44 PM (8 years ago)
Author:
suehring
Message:

deallocation of unused particle memory, formatting adjustments

Location:
palm/trunk/SOURCE
Files:
5 edited

Legend:

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

    r1930 r1936  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Call routine for deallocation of unused memory.
     22! Formatting adjustments
    2223!
    2324! Former revisions:
     
    120121
    121122    USE lpm_exchange_horiz_mod,                                                &
    122         ONLY:  lpm_exchange_horiz, lpm_move_particle
     123        ONLY:  dealloc_particles_array, lpm_exchange_horiz, lpm_move_particle
    123124
    124125    USE lpm_init_mod,                                                          &
     
    129130
    130131    USE particle_attributes,                                                   &
    131         ONLY:  collision_kernel, deleted_particles,                            &
     132        ONLY:  collision_kernel, deleted_particles, deallocate_memory,         &
    132133               dt_write_particle_data, dt_prel, end_time_prel,                 &
    133134               grid_particles, number_of_particles, number_of_particle_groups, &
    134                particles, particle_groups, prt_count, trlp_count_sum,          &
    135                time_prel,                                                      &
    136                time_write_particle_data, trlp_count_recv_sum, trnp_count_sum,  &
     135               particles, particle_groups, prt_count, step_dealloc,            &
     136               time_prel, time_write_particle_data, trlp_count_sum,            &
     137               trlp_count_recv_sum, trnp_count_sum,                            &
    137138               trnp_count_recv_sum, trrp_count_sum, trrp_count_recv_sum,       &
    138139               trsp_count_sum, trsp_count_recv_sum,                            &
     
    149150    INTEGER(iwp)       ::  je                 !<
    150151    INTEGER(iwp)       ::  js                 !<
     152    INTEGER(iwp), SAVE ::  lpm_count = 0      !<
    151153    INTEGER(iwp)       ::  k                  !<
    152154    INTEGER(iwp)       ::  ke                 !<
     
    381383!
    382384!-- Calculate the new liquid water content for each grid box
    383     IF ( cloud_droplets )  THEN
    384        CALL lpm_calc_liquid_water_content
     385    IF ( cloud_droplets )  CALL lpm_calc_liquid_water_content
     386!
     387!-- Deallocate unused memory
     388    IF ( deallocate_memory  .AND.  lpm_count == step_dealloc )  THEN
     389       CALL dealloc_particles_array
     390       lpm_count = 0
     391    ELSEIF ( deallocate_memory )  THEN
     392       lpm_count = lpm_count + 1
    385393    ENDIF
    386 
    387 
    388394
    389395!
  • palm/trunk/SOURCE/lpm_advec.f90

    r1930 r1936  
    1919! Current revisions:
    2020! ------------------
    21 !  
     21! Formatting adjustments
    2222!
    2323! Former revisions:
     
    264264          jlog = ( particles(n)%y + 0.5_wp * dy ) * ddy
    265265
    266           IF ( constant_flux_layer .AND. zv(n) - zw(nzb_s_inner(jlog,ilog)) < z_p )  THEN
     266          IF ( constant_flux_layer  .AND.                                      &
     267               zv(n) - zw(nzb_s_inner(jlog,ilog)) < z_p )  THEN
    267268!
    268269!--          Resolved-scale horizontal particle velocity is zero below z0.
     
    272273!
    273274!--             Determine the sublayer. Further used as index.
    274                 height_p     = ( zv(n) - zw(nzb_s_inner(jlog,ilog)) - z0_av_global )            &
    275                                      * REAL( number_of_sublayers, KIND=wp ) &
     275                height_p = ( zv(n) - zw(nzb_s_inner(jlog,ilog)) - z0_av_global ) &
     276                                     * REAL( number_of_sublayers, KIND=wp )    &
    276277                                     * d_z_p_z0
    277278!
     
    340341          ilog = ( particles(n)%x + 0.5_wp * dx ) * ddx
    341342          jlog = ( particles(n)%y + 0.5_wp * dy ) * ddy
    342           IF ( constant_flux_layer .AND. zv(n) - zw(nzb_s_inner(jlog,ilog)) < z_p )  THEN
     343          IF ( constant_flux_layer  .AND.                                      &
     344               zv(n) - zw(nzb_s_inner(jlog,ilog)) < z_p )  THEN
    343345
    344346             IF ( zv(n) - zw(nzb_s_inner(jlog,ilog)) < z0_av_global )  THEN
     
    352354!--             topography particle on u-grid can be above surface-layer height,
    353355!--             whereas it can be below on v-grid.
    354                 height_p     = ( zv(n) - zw(nzb_s_inner(jlog,ilog)) - z0_av_global ) &
    355                                   * REAL( number_of_sublayers, KIND=wp )    &
     356                height_p = ( zv(n) - zw(nzb_s_inner(jlog,ilog)) - z0_av_global ) &
     357                                  * REAL( number_of_sublayers, KIND=wp )       &
    356358                                  * d_z_p_z0
    357359!
     
    367369!--             friction velocity can become very small, resulting in a too
    368370!--             large particle speed.
    369                 us_int   = MAX( 0.5_wp * ( us(jlog,ilog) + us(jlog-1,ilog) ), &
     371                us_int   = MAX( 0.5_wp * ( us(jlog,ilog) + us(jlog-1,ilog) ),  &
    370372                                0.01_wp )   
    371373!
     
    376378!--             as sensitivity studies revealed no significant effect of
    377379!--             using the neutral solution also for un/stable situations.
    378                 v_int(n) = -vsws(jlog,ilog) / ( us_int * kappa + 1E-10_wp )          &
     380                v_int(n) = -vsws(jlog,ilog) / ( us_int * kappa + 1E-10_wp )    &
    379381                         * log_z_z0_int - v_gtrans
    380382
  • palm/trunk/SOURCE/lpm_exchange_horiz.f90

    r1930 r1936  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Deallocation of unused memory
    2222!
    2323! Former revisions:
     
    138138
    139139    PRIVATE
    140     PUBLIC lpm_exchange_horiz, lpm_move_particle, realloc_particles_array
     140    PUBLIC lpm_exchange_horiz, lpm_move_particle, realloc_particles_array,     &
     141           dealloc_particles_array
    141142
    142143    INTERFACE lpm_exchange_horiz
     
    152153    END INTERFACE realloc_particles_array
    153154
     155    INTERFACE dealloc_particles_array
     156       MODULE PROCEDURE dealloc_particles_array
     157    END INTERFACE dealloc_particles_array
    154158CONTAINS
    155159
     
    10571061    TYPE(particle_type), DIMENSION(500)            :: tmp_particles_s !<
    10581062
    1059 
    10601063    old_size = SIZE(grid_particles(k,j,i)%particles)
    10611064
     
    10971100 END SUBROUTINE realloc_particles_array
    10981101
     1102
     1103
     1104
     1105
     1106 SUBROUTINE dealloc_particles_array
     1107
     1108    IMPLICIT NONE
     1109
     1110    INTEGER(iwp) ::  i
     1111    INTEGER(iwp) ::  j
     1112    INTEGER(iwp) ::  k
     1113    INTEGER(iwp) :: old_size        !<
     1114    INTEGER(iwp) :: new_size        !<
     1115
     1116    LOGICAL                                        :: dealloc 
     1117
     1118    TYPE(particle_type), DIMENSION(:), ALLOCATABLE :: tmp_particles_d !<
     1119    TYPE(particle_type), DIMENSION(500)            :: tmp_particles_s !<
     1120
     1121    DO  i = nxl, nxr
     1122       DO  j = nys, nyn
     1123          DO  k = nzb+1, nzt
     1124!
     1125!--          Determine number of active particles
     1126             number_of_particles = prt_count(k,j,i)
     1127!
     1128!--          Determine allocated memory size
     1129             old_size = SIZE( grid_particles(k,j,i)%particles )
     1130!
     1131!--          Check for large unused memory
     1132             dealloc = ( ( number_of_particles < min_nr_particle .AND.         &
     1133                           old_size            > min_nr_particle )  .OR.       &
     1134                         ( number_of_particles > min_nr_particle .AND.         &
     1135                           old_size - number_of_particles *                    &
     1136                              ( 1.0_wp + 0.01_wp * alloc_factor ) > 0.0_wp ) )
     1137                         
     1138
     1139             IF ( dealloc )  THEN
     1140                IF ( number_of_particles < min_nr_particle )  THEN
     1141                   new_size = min_nr_particle
     1142                ELSE
     1143                   new_size = INT( number_of_particles * ( 1.0_wp + 0.01_wp * alloc_factor ) )
     1144                ENDIF
     1145
     1146                IF ( number_of_particles <= 500 )  THEN
     1147
     1148                   tmp_particles_s(1:number_of_particles) = grid_particles(k,j,i)%particles(1:number_of_particles)
     1149
     1150                   DEALLOCATE(grid_particles(k,j,i)%particles)
     1151                   ALLOCATE(grid_particles(k,j,i)%particles(new_size))
     1152
     1153                   grid_particles(k,j,i)%particles(1:number_of_particles)          = tmp_particles_s(1:number_of_particles)
     1154                   grid_particles(k,j,i)%particles(number_of_particles+1:new_size) = zero_particle
     1155
     1156                ELSE
     1157
     1158                   ALLOCATE(tmp_particles_d(number_of_particles))
     1159                   tmp_particles_d(1:number_of_particles) = grid_particles(k,j,i)%particles(1:number_of_particles)
     1160
     1161                   DEALLOCATE(grid_particles(k,j,i)%particles)
     1162                   ALLOCATE(grid_particles(k,j,i)%particles(new_size))
     1163
     1164                   grid_particles(k,j,i)%particles(1:number_of_particles)          = tmp_particles_d(1:number_of_particles)
     1165                   grid_particles(k,j,i)%particles(number_of_particles+1:new_size) = zero_particle
     1166
     1167                   DEALLOCATE(tmp_particles_d)
     1168
     1169                ENDIF
     1170
     1171             ENDIF
     1172          ENDDO
     1173       ENDDO
     1174    ENDDO
     1175
     1176 END SUBROUTINE dealloc_particles_array
     1177
     1178
    10991179END MODULE lpm_exchange_horiz_mod
  • palm/trunk/SOURCE/mod_particle_attributes.f90

    r1930 r1936  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! +deallocate_memory, step_dealloc
    2222!
    2323! Former revisions:
     
    8383                     offset_ocean_nzt_m1 = 0, particles_per_point = 1,         &
    8484                     particle_file_count = 0, radius_classes = 20,             &
    85                      sort_count = 0,                                           &
     85                     sort_count = 0, step_dealloc = 100,                       &
    8686                     total_number_of_particles,                                &
    8787                     trlp_count_sum, trlp_count_recv_sum, trrp_count_sum,      &
     
    9595    LOGICAL ::  all_or_nothing = .FALSE., average_impact = .FALSE.,            &
    9696                curvature_solution_effects = .FALSE.,                          &
     97                deallocate_memory = .TRUE.,                                    &
    9798                hall_kernel = .FALSE., particle_advection = .FALSE.,           &
    9899                random_start_position = .FALSE.,                               &
  • palm/trunk/SOURCE/package_parin.f90

    r1917 r1936  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! +deallocate_memory, step_dealloc
    2222!
    2323! Former revisions:
     
    154154        ONLY:  alloc_factor, bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,         &
    155155               collision_algorithm, collision_kernel,                          &
    156                curvature_solution_effects, density_ratio, dissipation_classes, &
    157                dt_min_part, dt_prel, dt_write_particle_data,                   &
    158                end_time_prel, initial_weighting_factor,                        &
     156               curvature_solution_effects, deallocate_memory, density_ratio,  &
     157               dissipation_classes, dt_min_part, dt_prel,                      &
     158               dt_write_particle_data, end_time_prel, initial_weighting_factor,&
    159159               init_aerosol_probabilistic, min_nr_particle,                    &
    160160               monodisperse_aerosols, n1, n2, n3, number_of_particle_groups,   &
     
    164164               radius_classes, random_start_position,                          &
    165165               read_particles_from_restartfile, rm1, rm2, rm3,                 &
    166                seed_follows_topography, s1, s2, s3, use_sgs_for_particles,     &
    167                vertical_particle_advection, write_particle_statistics
     166               seed_follows_topography, step_dealloc, s1, s2, s3,              &
     167               use_sgs_for_particles, vertical_particle_advection,             &
     168               write_particle_statistics
    168169
    169170    IMPLICIT NONE
     
    192193                                  bc_par_ns, bc_par_t, collision_algorithm,    &
    193194                                  collision_kernel, curvature_solution_effects,&
    194                                   density_ratio, dissipation_classes, dt_dopts,&
     195                                  deallocate_memory, density_ratio,            &
     196                                  dissipation_classes, dt_dopts,               &
    195197                                  dt_min_part, dt_prel,                        &
    196198                                  dt_write_particle_data,                      &
     
    206208                                  read_particles_from_restartfile,             &
    207209                                  rm1, rm2, rm3,                               &
    208                                   seed_follows_topography, s1, s2, s3,         &
    209                                   use_sgs_for_particles,                       &
     210                                  seed_follows_topography, step_dealloc,       &
     211                                  s1, s2, s3, use_sgs_for_particles,           &
    210212                                  vertical_particle_advection,                 &
    211213                                  write_particle_statistics
Note: See TracChangeset for help on using the changeset viewer.