Ignore:
Timestamp:
Jul 26, 2019 1:45:03 PM (5 years ago)
Author:
gronemeier
Message:

bugfix: do not assue that output arrays start with index 0

File:
1 edited

Legend:

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

    r4108 r4123  
    525525!--------------------------------------------------------------------------------------------------!
    526526SUBROUTINE binary_write_variable(                                         &
    527               file_id, var_id, bounds_start, bounds_end, bounds_origin,  &
    528               do_output, is_global,                                       &
     527              file_id, var_id, bounds_start, value_counts, bounds_origin, &
     528              is_global,                                                  &
    529529              var_int8_0d,   var_int8_1d,   var_int8_2d,   var_int8_3d,   &
    530530              var_int16_0d,  var_int16_1d,  var_int16_2d,  var_int16_3d,  &
     
    545545
    546546   INTEGER(iwp), DIMENSION(:), INTENT(IN) ::  bounds_origin  !< starting index of each dimension
    547    INTEGER(iwp), DIMENSION(:), INTENT(IN) ::  bounds_end     !< ending index of variable
    548547   INTEGER(iwp), DIMENSION(:), INTENT(IN) ::  bounds_start   !< starting index of variable
     548   INTEGER(iwp), DIMENSION(:), INTENT(IN) ::  value_counts   !< count of values along each dimension to be written
    549549
    550550   INTEGER(KIND=1), POINTER, INTENT(IN), OPTIONAL                               ::  var_int8_0d  !< output variable
     
    568568   INTEGER(iwp), POINTER, CONTIGUOUS, INTENT(IN), OPTIONAL, DIMENSION(:,:,:) ::  var_intwp_3d  !< output variable
    569569
    570    LOGICAL, INTENT(IN) ::  do_output  !< write output only if do_output = true
    571570   LOGICAL, INTENT(IN) ::  is_global  !< true if variable is global (same on all PE)
    572571
     
    594593   IF ( is_global )  CONTINUE  ! reqired to prevent compiler warning
    595594
    596    IF ( do_output )  THEN
     595   IF ( .NOT. ANY( value_counts == 0 ) )  THEN
    597596      WRITE( file_id )  var_id
    598597      WRITE( file_id )  bounds_start
    599       WRITE( file_id )  bounds_end
     598      WRITE( file_id )  value_counts
    600599      WRITE( file_id )  bounds_origin
    601600      !-- 8bit integer output
Note: See TracChangeset for help on using the changeset viewer.