Ignore:
Timestamp:
Mar 1, 2010 8:30:24 AM (14 years ago)
Author:
raasch
Message:

New:
---
Output in NetCDF4-format. New d3par-parameter netcdf_data_format.

(check_open, check_parameters, close_file, data_output_2d, data_output_3d, header, modules, netcdf, parin)

Modules to be loaded for compilation (mbuild) or job execution (mrun)
can be given in the configuration file using variable modules. Example:

%modules ifort/11.0.069:netcdf lcsgih parallel

This method replaces the (undocumented) mpilib-variable.

WARNING: All fixed settings of modules in the scripts mbuild, mrun, and subjob
have been removed! Please set the modules variable appropriately in your
configuration file. (mbuild, mrun, subjob)

Changed:


Parameters netcdf_64bit and netcdf_64bit_3d have been removed. Use
netcdf_data_format = 2 for choosing the classic 64bit-offset format (this is
the default). The offset-format can not be set independently for the
3d-output-data any more.

Parameters netcdf_format_mask, netcdf_format_mask_av, and variables
nc_format_mask, format_parallel_io removed. They are replaced by the new
parameter netcdf_data_format. (check_open, close_file,
data_output_mask, header, init_masks, modules, parin)

Errors:


bugfix in trunk/UTIL/Makefile: forgot to compile for interpret_config

Bugfix: timeseries data have to be collected by PE0 (user_statistics)

File:
1 edited

Legend:

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

    r484 r493  
    44! Current revisions:
    55! -----------------
    6 !
     6! Bugfix: timeseries data have to be collected by PE0
    77!
    88! Former revisions:
     
    2525    USE arrays_3d
    2626    USE indices
     27    USE netcdf_control
    2728    USE statistics
    2829    USE user
     
    3334
    3435    INTEGER ::  i, j, k, sr, tn
     36
     37    REAL, DIMENSION(dots_num_palm+1:dots_max) ::  ts_value_l
    3538
    3639
     
    7073!--    creates two time series for the absolut values of the horizontal
    7174!--    velocities u and v.
    72 !       ts_value(dots_num_palm+1,sr) = ABS( u_max )
    73 !       ts_value(dots_num_palm+2,sr) = ABS( v_max )
     75!       ts_value_l = 0.0
     76!       ts_value_l(dots_num_palm+1,sr) = ABS( u_max )
     77!       ts_value_l(dots_num_palm+2,sr) = ABS( v_max )
     78!
     79!--     Collect / send values to PE0, because only PE0 outputs the time series.
     80!--     CAUTION: Collection is done by taking the sum over all processors.
     81!--              You may have to normalize this sum, depending on the quantity
     82!--              that you like to calculate. For serial runs, nothing has to be
     83!--              done.
     84!--     HINT: If the time series value that you are calculating has the same
     85!--           value on all PEs, you can omit the MPI_ALLREDUCE call and
     86!--           assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
     87!#if defined( __parallel )
     88!       CALL MPI_ALLREDUCE( ts_value_l(dots_num_palm+1),                       &
     89!                           ts_value(dots_num_palm+1,sr),                      &
     90!                           dots_max-dots_num_palm, MPI_REAL, MPI_SUM, comm2d, &
     91!                           ierr )
     92!#else
     93!       ts_value(dots_num_palm+1:,sr) = ts_value_l
     94!#endif
    7495
    7596    ENDIF
Note: See TracChangeset for help on using the changeset viewer.