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/init_masks.f90

    r484 r493  
    4848    ALLOCATE( mask(max_masks,3,mask_xyz_dimension), &
    4949              mask_loop(max_masks,3,3) )
    50 !
    51 !-- Store netcdf file formats for masked data output in one shared array
    52     nc_format_mask(:,0) = netcdf_format_mask
    53     nc_format_mask(:,1) = netcdf_format_mask_av
    5450   
    55     IF ( ANY( nc_format_mask == 3 ) .OR. ANY( nc_format_mask == 4 )) THEN
    56        format_parallel_io = .TRUE.
    57     ENDIF
    58 
    59     IF ( ANY( nc_format_mask < 1 ) .OR. ANY( nc_format_mask > 4 ) )  THEN
    60        WRITE( message_string, * )  'illegal value: netcdf_format_mask and ', &
    61             'netcdf_format_mask_av must be either 1, 2, 3 or 4'
    62        IF ( ANY( nc_format_mask == 3 ) .OR. ANY( nc_format_mask == 4 ) )  THEN
    63           message_string = TRIM( message_string ) // '&NetCDF file formats '// &
    64                '3 (NetCDF 4) and 4 (NetCDF 4 Classic model)'// &
    65                '&are currently not supported (not yet tested).'
    66        ENDIF
     51!
     52!-- Parallel mask output not yet tested
     53    IF ( netcdf_data_format > 2 )  THEN
     54       message_string = 'NetCDF file formats '//                         &
     55                        '3 (NetCDF 4) and 4 (NetCDF 4 Classic model)'//  &
     56                        '&are currently not supported (not yet tested).'
    6757       CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
    6858    ENDIF
     
    162152!
    163153!-- Global arrays are required by define_netcdf_header.
    164     IF ( format_parallel_io )  THEN
    165        ALLOCATE( mask_i_global(max_masks,nx+1), &
    166                  mask_j_global(max_masks,ny+1), &
    167                  mask_k_global(max_masks,nz+1) )
    168        mask_i_global = -1; mask_j_global = -1; mask_k_global = -1
    169     ELSEIF ( myid == 0 )  THEN
     154    IF ( myid == 0  .OR.  netcdf_data_format > 2 )  THEN
    170155       ALLOCATE( mask_i_global(max_masks,nx+1), &
    171156                 mask_j_global(max_masks,ny+1), &
     
    472457       CALL MPI_BARRIER( comm2d, ierr )
    473458       
    474        IF ( format_parallel_io )  THEN 
     459       IF ( netcdf_data_format > 2 )  THEN 
    475460         
    476           CALL MPI_BCAST( mask_i_global(mid,:), nx+1, MPI_INTEGER, 0, comm2d, ierr )
    477           CALL MPI_BCAST( mask_j_global(mid,:), ny+1, MPI_INTEGER, 0, comm2d, ierr )
    478           CALL MPI_BCAST( mask_k_global(mid,:), nz+1, MPI_INTEGER, 0, comm2d, ierr )
     461          CALL MPI_BCAST( mask_i_global(mid,:), nx+1, MPI_INTEGER, 0, comm2d, &
     462                          ierr )
     463          CALL MPI_BCAST( mask_j_global(mid,:), ny+1, MPI_INTEGER, 0, comm2d, &
     464                          ierr )
     465          CALL MPI_BCAST( mask_k_global(mid,:), nz+1, MPI_INTEGER, 0, comm2d, &
     466                          ierr )
    479467         
    480468       ENDIF
     
    496484
    497485 CONTAINS
     486
    498487    SUBROUTINE set_mask_locations( dim, dxyz, dxyz_string, nxyz, nxyz_string, &
    499488                                   lb, ub )
Note: See TracChangeset for help on using the changeset viewer.