Ignore:
Timestamp:
Feb 5, 2016 1:06:51 PM (8 years ago)
Author:
gronemeier
Message:

Bugfix:calculation of time levels for parallel NetCDF output

File:
1 edited

Legend:

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

    r1702 r1745  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Bugfix: check data output intervals to be /= 0.0 in case of parallel NetCDF4
    2222!
    2323! Former revisions:
     
    38353835    IF ( netcdf_data_format > 4 )  THEN
    38363836
     3837!
     3838!--    Check if any of the follwoing data output interval is 0.0s, which is
     3839!--    not allowed for parallel output.
     3840       CALL check_dt_do( dt_do3d,    'dt_do3d'    )
     3841       CALL check_dt_do( dt_do2d_xy, 'dt_do2d_xy' )
     3842       CALL check_dt_do( dt_do2d_xz, 'dt_do2d_xz' )
     3843       CALL check_dt_do( dt_do2d_yz, 'dt_do2d_yz' )
     3844
    38373845       ntdim_3d(0)    = INT( ( end_time - skip_time_do3d ) / dt_do3d )
    38383846       IF ( do3d_at_begin ) ntdim_3d(0) = ntdim_3d(0) + 1
     
    38503858       ntdim_2d_xz(1) = ntdim_3d(1)
    38513859       ntdim_2d_yz(1) = ntdim_3d(1)
    3852 
     3860             write(9,*) "ntdim_3d(av)=",ntdim_3d(0)
     3861             CALL local_flush(9)
    38533862    ENDIF
    38543863
     
    43334342    CALL user_check_parameters
    43344343
     4344 CONTAINS
     4345
     4346!------------------------------------------------------------------------------!
     4347! Description:
     4348! ------------
     4349!> Check the length of data output intervals. In case of parallel NetCDF output
     4350!> the time levels of the output files need to be fixed. Therefore setting the
     4351!> output interval to 0.0s (usually used to output each timestep) is not
     4352!> possible as long as a non-fixed timestep is used.
     4353!------------------------------------------------------------------------------!
     4354
     4355    SUBROUTINE check_dt_do( dt_do, dt_do_name )
     4356
     4357       IMPLICIT NONE
     4358
     4359       CHARACTER (LEN=*), INTENT (IN) :: dt_do_name !< parin variable name
     4360
     4361       REAL(wp), INTENT (INOUT)       :: dt_do      !< data output interval
     4362
     4363       IF ( dt_do == 0.0_wp )  THEN
     4364          IF ( dt_fixed )  THEN
     4365             WRITE( message_string, '(A,F9.4,A)' )  'Output at every '  //  &
     4366                    'timestep is desired (' // dt_do_name // ' = 0.0).&'//  &
     4367                    'Setting the output interval to the fixed timestep '//  &
     4368                    'dt = ', dt, 's.'
     4369             CALL message( 'check_parameters', 'PA0060', 0, 0, 0, 6, 0 )
     4370             dt_do = dt
     4371          ELSE
     4372             message_string = dt_do_name // ' = 0.0 while using a ' //      &
     4373                              'variable timestep and parallel netCDF4 ' //  &
     4374                              'is not allowed.'
     4375             CALL message( 'check_parameters', 'PA0081', 1, 2, 0, 6, 0 )
     4376          ENDIF
     4377       ENDIF
     4378
     4379    END SUBROUTINE check_dt_do
    43354380
    43364381 END SUBROUTINE check_parameters
Note: See TracChangeset for help on using the changeset viewer.