Changeset 4778 for palm


Ignore:
Timestamp:
Nov 9, 2020 1:40:05 PM (3 years ago)
Author:
raasch
Message:

first preliminary version for output of particle data time series

Location:
palm/trunk/SOURCE
Files:
1 added
6 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/Makefile

    r4750 r4778  
    2525# -----------------
    2626# $Id$
     27# particle output routine and dependencies added
     28#
     29# 4750 2020-10-16 14:27:48Z suehring
    2730# Bugfix, missing dependency on indoor_model_mod added
    2831#
     
    233236        data_output_flight.f90\
    234237        data_output_mask.f90 \
     238        data_output_particle_mod.f90 \
    235239        data_output_profiles.f90 \
    236240        data_output_spectra.f90 \
     
    551555data_output_netcdf4_module.o: \
    552556        mod_kinds.o
     557data_output_particle_mod.o: \
     558        data_output_netcdf4_module.o \
     559        modules.o \
     560        mod_kinds.o \
     561        mod_particle_attributes.o \
     562        shared_memory_io_mod.o
    553563data_output_profiles.o: \
    554564        cpulog_mod.o \
     
    768778        basic_constants_and_equations_mod.o \
    769779        cpulog_mod.o \
     780        data_output_particle_mod.o \
    770781        exchange_horiz_mod.o \
    771782        mod_kinds.o \
  • palm/trunk/SOURCE/check_open.f90

    r4652 r4778  
    2525! -----------------
    2626! $Id$
     27! local filename for output of particle time series changed
     28!
     29! 4652 2020-08-27 08:51:55Z raasch
    2730! Routine fortran_sleep has been moved to module posix_interface
    2831!
     
    9981001!
    9991002!--       Set filename
    1000           filename = 'DATA_1D_PTS_NETCDF' // TRIM( coupling_char )
     1003          filename = 'DATA_1D_SPTS_NETCDF' // TRIM( coupling_char )
    10011004
    10021005!
  • palm/trunk/SOURCE/lagrangian_particle_model_mod.f90

    r4731 r4778  
    2424! -----------------
    2525! $Id$
     26! output of particle time series added
     27!
     28! 4731 2020-10-07 13:25:11Z schwenkel
    2629! Move exchange_horiz from time_integration to modules
    2730!
     
    209212    USE cpulog,                                                                                    &
    210213        ONLY:  cpu_log, log_point, log_point_s
     214
     215    USE data_output_particle_mod,                                                                  &
     216        ONLY:  dop_active,                                                                         &
     217               dop_finalize,                                                                       &
     218               dop_init,                                                                           &
     219               dop_output_tseries,                                                                 &
     220               dop_prt_axis_dimension,                                                             &
     221               dop_last_active_particle
    211222
    212223    USE indices,                                                                                   &
     
    266277               surf_lsm_h,                                                                         &
    267278               surf_usm_h
    268 
    269 !-- Next lines are in preparation for the output of particle data
    270 !    USE data_output_particle_mod,                                              &
    271 !        ONLY:  dop_active, dop_init, dop_output_tseries
    272279
    273280#if defined( __parallel )
     
    326333    INTEGER(iwp) ::  trnp_count_sum                               !< parameter for particle exchange of PEs
    327334
     335    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  id_counter !< number of particles initialized in each grid box
    328336    INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE ::  seq_random_array_particles   !< sequence of random array for particle
    329337
     
    410418    PRIVATE
    411419
    412     PUBLIC lpm_parin,                                                                              &
    413            lpm_header,                                                                             &
    414            lpm_init_arrays,                                                                        &
    415            lpm_init,                                                                               &
    416            lpm_actions,                                                                            &
     420    PUBLIC lagrangian_particle_model
     421
     422    PUBLIC lpm_actions,                                                                            &
     423           lpm_check_parameters,                                                                   &
    417424           lpm_data_output_ptseries,                                                               &
    418425           lpm_exchange_horiz_bounds,                                                              &
     426           lpm_header,                                                                             &
     427           lpm_init,                                                                               &
    419428           lpm_interaction_droplets_ptq,                                                           &
     429           lpm_init_arrays,                                                                        &
     430           lpm_last_actions,                                                                       &
     431           lpm_parin,                                                                              &
     432           lpm_rrd_global,                                                                         &
     433           lpm_rrd_local,                                                                          &
    420434           lpm_rrd_local_particles,                                                                &
    421            lpm_wrd_local,                                                                          &
    422            lpm_rrd_global,                                                                         &
    423435           lpm_wrd_global,                                                                         &
    424            lpm_rrd_local,                                                                          &
    425            lpm_check_parameters
    426 
    427     PUBLIC lagrangian_particle_model
     436           lpm_wrd_local
    428437
    429438    INTERFACE lpm_check_parameters
     
    533542       MODULE PROCEDURE dealloc_particles_array
    534543    END INTERFACE dealloc_particles_array
     544
     545    INTERFACE lpm_last_actions
     546       MODULE PROCEDURE lpm_last_actions
     547    END INTERFACE lpm_last_actions
    535548
    536549    INTERFACE lpm_sort_and_delete
     
    629642       collision_kernel,                                                                           &
    630643       curvature_solution_effects,                                                                 &
     644       data_output_pts,                                                                            &
    631645       deallocate_memory,                                                                          &
    632646       density_ratio,                                                                              &
     
    651665       particle_advection_interpolation,                                                           &
    652666       particle_maximum_age,                                                                       &
    653        part_output,                                                                                &
    654        part_inc,                                                                                   &
    655        part_percent,                                                                               &
     667       pts_id_file,                                                                                &
     668       pts_increment,                                                                              &
     669       pts_percentage,                                                                             &
    656670       pdx,                                                                                        &
    657671       pdy,                                                                                        &
     
    861875 SUBROUTINE lpm_check_parameters
    862876
     877    LOGICAL ::  id_file_exists = .FALSE.
     878
    863879!
    864880!-- Collision kernels:
     
    880896
    881897    END SELECT
     898
    882899    IF ( collision_kernel(6:9) == 'fast' )  use_kernel_tables = .TRUE.
    883900
     
    897914       message_string = 'nested runs in combination with cloud droplets ' //                       &
    898915                        'is not implemented'
    899           CALL message( 'lpm_check_parameters', 'PA0687', 1, 2, 0, 6, 0 )
     916       CALL message( 'lpm_check_parameters', 'PA0687', 1, 2, 0, 6, 0 )
    900917    ENDIF
    901918
     919    IF ( pts_increment > 1  .AND.  pts_percentage < 100.0_wp )  THEN
     920       message_string = 'pts_increment and pts_percentage cannot be set both '
     921       CALL message( 'lpm_check_parameters', 'PA0...', 1, 2, 0, 6, 0 )
     922    ENDIF
     923
     924    IF ( pts_increment < 1 )  THEN
     925       message_string = 'pts_increment must be > 1'
     926       CALL message( 'lpm_check_parameters', 'PA0...', 1, 2, 0, 6, 0 )
     927    ENDIF
     928
     929    IF ( pts_percentage > 100.0_wp )  THEN
     930       message_string = 'pts_percentage must be < 100'
     931       CALL message( 'lpm_check_parameters', 'PA0...', 1, 2, 0, 6, 0 )
     932    ENDIF
     933
     934    INQUIRE( FILE = pts_id_file, EXIST = id_file_exists )
     935#if defined( __netcdf4_parallel )
     936!
     937!-- Check if individual particles timeseries is set
     938    IF ( pts_increment  > 1  .AND.  dt_dopts /= 9999999.9_wp  .OR.                                 &
     939         pts_percentage < 100.0_wp  .AND.  dt_dopts /= 9999999.9_wp  .OR.                          &
     940         id_file_exists  .AND.  dt_dopts /= 9999999.9_wp  )                                        &
     941    THEN
     942       dop_active = .TRUE.
     943    ENDIF
     944#endif
    902945
    903946 END SUBROUTINE lpm_check_parameters
     
    948991    INTEGER(iwp) ::  j                           !<
    949992    INTEGER(iwp) ::  k                           !<
     993
     994    LOGICAL  ::  read_restart                    !<
    950995
    951996    REAL(wp) ::  div                             !<
     
    12291274!-- For the first model run of a possible job chain initialize the particles, otherwise read the
    12301275!-- particle data from restart file.
     1276    read_restart = .FALSE.
    12311277    IF ( TRIM( initializing_actions ) == 'read_restart_data'                                       &
    12321278         .AND.  read_particles_from_restartfile )  THEN
    12331279       CALL lpm_rrd_local_particles
     1280
     1281       read_restart = .TRUE.
    12341282    ELSE
    12351283!
    12361284!--    Allocate particle arrays and set attributes of the initial set of particles, which can be
    12371285!--    also periodically released at later times.
    1238        ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                                         &
    1239                  grid_particles(nzb+1:nzt,nys:nyn,nxl:nxr) )
     1286       ALLOCATE( grid_particles(nzb+1:nzt,nys:nyn,nxl:nxr),                                        &
     1287                 id_counter(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                                        &
     1288                 prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    12401289
    12411290       number_of_particles = 0
     
    12431292!
    12441293!--    Initialize counter for particle IDs
    1245        grid_particles%id_counter = 1
     1294       id_counter = 1
    12461295!
    12471296!--    Initialize all particles with dummy values (otherwise errors may occur within restart runs).
     
    13141363
    13151364!
    1316 !-- next line is in preparation for particle data output
    1317 !    CALL dop_init
     1365!-- Output of particle time series
     1366    IF ( dop_active )  THEN
     1367       CALL dop_init( read_restart )
     1368    ENDIF
    13181369
    13191370!
     
    15201571    prt_count   = local_count
    15211572!
    1522 !-- Calculate particle IDs
     1573!-- Calculate particle IDs (for new particles only)
    15231574    DO  ip = nxl, nxr
    15241575       DO  jp = nys, nyn
     
    15271578             IF ( number_of_particles <= 0 )  CYCLE
    15281579             particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
    1529 
    1530              DO  n = local_start(kp,jp,ip), number_of_particles  !only new particles
    1531 
    1532                 particles(n)%id = 10000_idp**3 * grid_particles(kp,jp,ip)%id_counter +             &
    1533                                   10000_idp**2 * kp + 10000_idp * jp + ip
     1580             DO  n = local_start(kp,jp,ip), number_of_particles
     1581
     1582                particles(n)%id = 10000_idp**3 * id_counter(kp,jp,ip) + 10000_idp**2 * kp +        &
     1583                                  10000_idp * jp + ip
    15341584!
    15351585!--             Count the number of particles that have been released before
    1536                 grid_particles(kp,jp,ip)%id_counter = grid_particles(kp,jp,ip)%id_counter + 1
     1586                id_counter(kp,jp,ip) = id_counter(kp,jp,ip) + 1
    15371587
    15381588             ENDDO
    1539 
    15401589          ENDDO
    15411590       ENDDO
     
    26822731    CALL cpu_log( log_point(36), 'data_output_ptseries', 'start' )
    26832732
     2733    IF ( dop_active )  THEN
     2734       CALL dop_output_tseries
     2735    ENDIF
     2736
    26842737    IF ( myid == 0 )  THEN
    26852738!
     
    30523105       FLUSH(9)
    30533106
    3054        ALLOCATE( prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                                         &
    3055                  grid_particles(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    3056 
    3057        ALLOCATE( prt_global_index(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     3107       ALLOCATE( grid_particles(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                                    &
     3108                 id_counter(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                                        &
     3109                 prt_count(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                                         &
     3110                 prt_global_index(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     3111
    30583112!
    30593113!--    Open restart file for read, if not already open, and do not allow usage of shared-memory I/O
     
    30683122
    30693123       prt_count = 0
     3124       CALL rrd_mpi_io( 'id_counter', id_counter )
    30703125       CALL rrd_mpi_io( 'prt_count', prt_count )
    30713126       CALL rrd_mpi_io( 'prt_global_index', prt_global_index )
     
    31473202    LOGICAL, INTENT(OUT)  ::  found
    31483203
    3149     REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) ::  tmp_3d   !<
    3150 
     3204    REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) ::  tmp_3d          !<
     3205    INTEGER(iwp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) ::  tmp_3d_int  !<
    31513206
    31523207    found = .TRUE.
    31533208
    31543209    SELECT CASE ( restart_string(1:length) )
     3210
     3211        CASE ( 'id_counter' )
     3212           IF ( .NOT. ALLOCATED( id_counter ) )  THEN
     3213              ALLOCATE( id_counter(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     3214           ENDIF
     3215           IF ( k == 1 )  READ ( 13 )  tmp_3d_int
     3216           id_counter(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                 &
     3217              tmp_3d_int(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    31553218
    31563219        CASE ( 'pc_av' )
     
    33493412#endif
    33503413
     3414       IF ( ALLOCATED( id_counter ) )  THEN
     3415          CALL wrd_write_string( 'id_counter' )
     3416          WRITE ( 14 )  id_counter
     3417       ENDIF
    33513418
    33523419       IF ( ALLOCATED( seq_random_array_particles ) )  THEN
     
    33553422       ENDIF
    33563423
    3357 
    33583424    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
    3359 
    33603425
    33613426       IF ( ALLOCATED( seq_random_array_particles ) )  THEN
     
    33963461       ENDIF
    33973462
    3398        CALL wrd_mpi_io( 'prt_count', prt_count )
     3463       CALL wrd_mpi_io( 'id_counter', id_counter )
     3464       CALL wrd_mpi_io( 'prt_count',  prt_count )
    33993465
    34003466       start_index = start_index_on_pe
     
    34373503       WRITE ( 14 )  curvature_solution_effects
    34383504
     3505       CALL wrd_write_string( 'dop_last_active_particle' )
     3506       WRITE ( 14 )  dop_last_active_particle
     3507
     3508       CALL wrd_write_string( 'dop_prt_axis_dimension' )
     3509       WRITE ( 14 )  dop_prt_axis_dimension
     3510
    34393511       CALL wrd_write_string( 'interpolation_simple_corrector' )
    34403512       WRITE ( 14 )  interpolation_simple_corrector
     
    34593531       CALL wrd_mpi_io( 'bc_par_ns', bc_par_ns )
    34603532       CALL wrd_mpi_io( 'bc_par_t', bc_par_t )
     3533       CALL wrd_mpi_io( 'dop_last_active_particle', dop_last_active_particle )
     3534       CALL wrd_mpi_io( 'dop_prt_axis_dimension', dop_prt_axis_dimension )
    34613535       CALL wrd_mpi_io( 'last_particle_release_time', last_particle_release_time )
    34623536       CALL wrd_mpi_io( 'number_of_particle_groups', number_of_particle_groups )
     
    35083582          READ ( 13 )  curvature_solution_effects
    35093583
     3584       CASE ( 'dop_last_active_particle' )
     3585          READ ( 13 )  dop_last_active_particle
     3586
     3587       CASE ( 'dop_prt_axis_dimension' )
     3588          READ ( 13 )  dop_prt_axis_dimension
     3589
    35103590       CASE ( 'interpolation_simple_corrector' )
    35113591          READ ( 13 )  interpolation_simple_corrector
     
    35513631    CALL rrd_mpi_io( 'bc_par_ns', bc_par_ns )
    35523632    CALL rrd_mpi_io( 'bc_par_t', bc_par_t )
     3633    CALL rrd_mpi_io( 'dop_prt_axis_dimension', dop_prt_axis_dimension )
     3634    CALL rrd_mpi_io( 'dop_last_active_particle', dop_last_active_particle )
    35533635    CALL rrd_mpi_io( 'last_particle_release_time', last_particle_release_time )
    35543636    CALL rrd_mpi_io( 'number_of_particle_groups', number_of_particle_groups )
     
    35773659
    35783660 END SUBROUTINE lpm_rrd_global_mpi
     3661
     3662
     3663!------------------------------------------------------------------------------!
     3664! Description:
     3665! ------------
     3666!> Last actions before PALM finishes.
     3667!------------------------------------------------------------------------------!
     3668 SUBROUTINE lpm_last_actions
     3669
     3670!
     3671!-- Close NETCDF file for individual particle timeseries
     3672    IF ( dop_active )  THEN
     3673       CALL dop_finalize
     3674    ENDIF
     3675
     3676 END SUBROUTINE lpm_last_actions
    35793677
    35803678
  • palm/trunk/SOURCE/mod_particle_attributes.f90

    r4677 r4778  
    2424! -----------------
    2525! $Id$
     26! variables for particle output renamed, id counter removed from particle type
     27!
     28! 4677 2020-09-14 07:55:28Z raasch
    2629! file re-formatted to follow the PALM coding standard
    2730!
     
    6063    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10 !< maximum allowed number of particle groups
    6164
    62     CHARACTER(LEN=varnamelength), DIMENSION(50) ::  part_output = ' '  !< namelist parameter
     65    CHARACTER(LEN=64)                           ::  pts_id_file = ''  !< namelist parameter
     66    CHARACTER(LEN=varnamelength), DIMENSION(50) ::  data_output_pts = ''    !< namelist parameter
    6367
    6468    INTEGER(iwp) ::  dissipation_classes = 10                     !< namelist parameter (see documentation)
     
    7175                                                                  !< prt_count)
    7276    INTEGER(iwp) ::  number_of_particle_groups = 1                !< namelist parameter (see documentation)
    73     INTEGER(iwp) ::  part_inc = 1                                 !< increment of particles in output file
     77    INTEGER(iwp) ::  pts_increment = 1                            !< increment of particles in output file
    7478
    7579    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count  !< 3d array of number of particles of every grid box
     
    8488                                                          !< number)
    8589    REAL(wp) ::  particle_advection_start = 0.0_wp        !< namelist parameter (see documentation)
    86     REAL(wp) ::  part_percent = 100.0_wp                  !< percentage of particles in output file
     90    REAL(wp) ::  pts_percentage = 100.0_wp                !< percentage of particles in output file
    8791
    8892    TYPE, PUBLIC ::  particle_type
     
    115119    END TYPE particle_type
    116120
    117     TYPE(particle_type), DIMENSION(:), POINTER ::  particles       !< Particle array for this grid cell
    118     TYPE(particle_type)                        ::  zero_particle   !< zero particle to avoid weird thinge
     121    TYPE(particle_type), DIMENSION(:), POINTER ::  particles      !< Particle array for this grid cell
     122    TYPE(particle_type)                        ::  zero_particle  !< zero particle to avoid weird things
    119123
    120124    TYPE particle_groups_type
     
    129133
    130134    TYPE  grid_particle_def
    131         INTEGER(iwp), DIMENSION(0:7)               ::  start_index        !< start particle index for current block
    132         INTEGER(iwp), DIMENSION(0:7)               ::  end_index          !< end particle index for current block
    133         INTEGER(iwp)                               ::  id_counter         !< particle id counter
    134         LOGICAL                                    ::  time_loop_done     !< timestep loop for particle advection
    135         TYPE(particle_type), POINTER, DIMENSION(:) ::  particles          !< Particle array for this grid cell
     135        INTEGER(iwp), DIMENSION(0:7)               ::  start_index     !< start particle index for current block
     136        INTEGER(iwp), DIMENSION(0:7)               ::  end_index       !< end particle index for current block
     137        LOGICAL                                    ::  time_loop_done  !< timestep loop for particle advection
     138        TYPE(particle_type), POINTER, DIMENSION(:) ::  particles       !< Particle array for this grid cell
    136139    END TYPE grid_particle_def
    137140
  • palm/trunk/SOURCE/module_interface.f90

    r4768 r4778  
    2424! -----------------
    2525! $Id$
     26! routine required for output of particle time series added
     27!
     28! 4768 2020-11-02 19:11:23Z suehring
    2629! Enable 3D data output also with 64-bit precision
    2730!
     
    399402               lpm_init,                                                                           &
    400403               lpm_init_arrays,                                                                    &
     404               lpm_last_actions,                                                                   &
    401405               lpm_parin,                                                                          &
    402406               lpm_rrd_global,                                                                     &
     
    20652069
    20662070    CALL dynamics_last_actions
    2067 
     2071    IF ( particle_advection )   CALL lpm_last_actions
    20682072    IF ( user_module_enabled )  CALL user_last_actions
    20692073
  • palm/trunk/SOURCE/shared_memory_io_mod.f90

    r4629 r4778  
    2525! -----------------
    2626! $Id$
     27! additions for output of particle time series
     28!
     29! 4629 2020-07-29 09:37:56Z raasch
    2730! support for MPI Fortran77 interface (mpif.h) removed
    2831!
     
    151154    TYPE, PUBLIC ::  sm_class  !<
    152155
    153        INTEGER(iwp) ::  nr_io_pe_per_node = 2         !< typical configuration, 2 sockets per node
     156       INTEGER(iwp) ::  nr_io_pe_per_node             !< typical configuration, 2 sockets per node
    154157       LOGICAL      ::  no_shared_Memory_in_this_run  !<
    155158
     
    185188          PROCEDURE, PASS(this), PUBLIC ::  sm_free_shared
    186189          PROCEDURE, PASS(this), PUBLIC ::  sm_init_comm
    187           PROCEDURE, PASS(this), PUBLIC ::  sm_init_part
     190          PROCEDURE, PASS(this), PUBLIC ::  sm_init_data_output_particles
    188191          PROCEDURE, PASS(this), PUBLIC ::  sm_node_barrier
    189192#if defined( __parallel )
     
    232235    LOGICAL, INTENT(IN) ::  sm_active  !< flag to activate shared-memory IO
    233236
     237    this%nr_io_pe_per_node = 2
     238
    234239    IF ( PRESENT( comm_input ) )  THEN
    235240       this%comm_model = comm_input
     
    414419
    415420!
    416 !-- TODO: short description required, about the meaning of the following routine
    417 !--       part must be renamed particles!
    418  SUBROUTINE sm_init_part( this )
     421!-- Initializing setup for output of particle time series.
     422!-- This output always uses a shared memory to reduce the number of particle transfers.
     423 SUBROUTINE sm_init_data_output_particles( this )
    419424
    420425    IMPLICIT NONE
     
    430435    LOGICAL :: sm_active  !<
    431436
     437
     438    this%nr_io_pe_per_node = 2
    432439
    433440    sm_active       = .TRUE.   ! particle IO always uses shared memory
     
    505512
    506513       WRITE( *, * ) 'shared_memory_io_mod: internal error'
    507        WRITE( *, * ) 'only 2 or 4 shared memory groups per node are allowed'
     514       WRITE( *, * ) 'only 1, 2 or 4 shared memory groups per node are allowed '
     515       WRITE( *, * ) 'here, ', this%nr_io_pe_per_node, ' groups have been set'
    508516       STOP
    509517
     
    540548#endif
    541549
    542 !    write(9,'(a,8i7)') 'sm_init_comm_part ',this%sh_rank,this%sh_npes,this%io_rank,this%io_npes
    543 
    544  END SUBROUTINE sm_init_part
     550 END SUBROUTINE sm_init_data_output_particles
    545551
    546552!--------------------------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.