Changeset 4123 for palm


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

Location:
palm/trunk
Files:
4 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
  • palm/trunk/SOURCE/data_output_module.f90

    r4116 r4123  
    8989      CHARACTER(LEN=charlen) ::  data_type = ''       !< data type
    9090      CHARACTER(LEN=charlen) ::  name                 !< variable name
    91       INTEGER(iwp)           ::  id = 0               !< id within file
     91      INTEGER(iwp)           ::  id = -1              !< id within file
    9292      LOGICAL                ::  is_global = .FALSE.  !< true if global variable
    9393      CHARACTER(LEN=charlen), DIMENSION(:), ALLOCATABLE ::  dimension_names  !< list of dimension names
     
    9999      CHARACTER(LEN=charlen) ::  data_type = ''       !< data type
    100100      CHARACTER(LEN=charlen) ::  name                 !< dimension name
    101       INTEGER(iwp)           ::  id = 0               !< dimension id within file
     101      INTEGER(iwp)           ::  id = -1              !< dimension id within file
    102102      INTEGER(iwp)           ::  length               !< length of dimension
    103103      INTEGER(iwp)           ::  length_mask          !< length of masked dimension
    104       INTEGER(iwp)           ::  var_id = 0           !< associated variable id within file
     104      INTEGER(iwp)           ::  var_id = -1          !< associated variable id within file
    105105      LOGICAL                ::  is_masked = .FALSE.  !< true if masked
    106106      INTEGER(iwp),    DIMENSION(2)              ::  bounds                !< lower and upper bound of dimension
     
    127127      CHARACTER(LEN=charlen) ::  format = ''        !< file format
    128128      CHARACTER(LEN=charlen) ::  name = ''          !< file name
    129       INTEGER(iwp)           ::  id = 0             !< id of file
     129      INTEGER(iwp)           ::  id = -1            !< id of file
    130130      LOGICAL                ::  is_init = .FALSE.  !< true if initialized
    131131      TYPE(attribute_type), DIMENSION(:), ALLOCATABLE ::  attributes  !< list of attributes
     
    965965               ALLOCATE( dimension%masked_values_realwp(0:dimension%length_mask-1) )
    966966               j = 0
    967                DO  i = 0, dimension%length-1
     967               DO  i = dimension%bounds(1), dimension%bounds(2)   !> @todo change loop also for other data types
    968968                  IF ( dimension%mask(i) )  THEN
    969969                     dimension%masked_values_realwp(j) = dimension%values_realwp(i)
     
    10851085! ------------
    10861086!> Add variable to database.
     1087!> Example call:
     1088!>   dom_def_var( filename =  'DATA_OUTPUT_3D', &
     1089!>                name = 'u', &
     1090!>                dimension_names = (/'x   ', 'y   ', 'z   ', 'time'/), &
     1091!>                output_type = 'real32' )
     1092!> @note The order of dimensions must match in reversed order to the dimensions of the
     1093!>       corresponding variable array. The last given dimension can also be non-existent within the
     1094!>       variable array if at any given call of 'dom_write_var' for this variable, the last
     1095!>       dimension has only a single index.
     1096!>       Hence, the array 'u' must be allocated with dimension 'x' as its last dimension, preceded
     1097!>       by 'y', then 'z', and 'time' being the first dimension. If at any given write statement,
     1098!>       only a single index of dimension 'time' is to be written, the dimension can be non-present
     1099!>       in the variable array leaving dimension 'z' as the first dimension.
     1100!>       So, the variable array needs to be allocated like either:
     1101!>          ALLOCATE( u(<time>,<z>,<y>,<x>) )
     1102!>       or
     1103!>          ALLOCATE( u(<z>,<y>,<x>) )
    10871104!--------------------------------------------------------------------------------------------------!
    10881105FUNCTION dom_def_var( filename, name, dimension_names, output_type, is_global ) &
     
    11231140
    11241141   variable%dimension_names = dimension_names
     1142   variable%dimension_ids = -1
    11251143   variable%data_type = TRIM( output_type )
    11261144
     
    25782596!>                  name = 'u', &
    25792597!>                  var_real64_3d = u, &
    2580 !>                  bounds_start = (/nzb, nys, nxl/), &
    2581 !>                  bounds_end = (/nzt, nyn, nxr/)  )
     2598!>                  bounds_start = (/nxl, nys, nzb, time_step/), &
     2599!>                  bounds_end = (/nxr, nyn, nzt, time_step/)  )
     2600!> @note The order of dimension bounds must match to the order of dimensions given in call
     2601!>       'dom_def_var'. I.e., the corresponding variable definition should be like:
     2602!>          dom_def_var( filename =  'DATA_OUTPUT_3D', &
     2603!>                       name = 'u', &
     2604!>                       dimension_names = (/'x   ', 'y   ', 'z   ', 'time'/), &
     2605!>                       output_type = <desired-output-type> )
    25822606!--------------------------------------------------------------------------------------------------!
    25832607FUNCTION dom_write_var( filename, name, bounds_start, bounds_end,       &
     
    26062630   INTEGER(iwp) ::  var_id               !< variable ID
    26072631
    2608    INTEGER(iwp), DIMENSION(:),   INTENT(IN)  ::  bounds_end        !< end index (upper bound) of variable at each dimension
    2609    INTEGER(iwp), DIMENSION(:),   INTENT(IN)  ::  bounds_start      !< start index (lower bound) of variable at each dimension
    2610    INTEGER(iwp), DIMENSION(:),   ALLOCATABLE ::  bounds_dim_start  !< start index (lower bound) of each dimension of variable
    2611    INTEGER(iwp), DIMENSION(:),   ALLOCATABLE ::  bounds_end_new    !< start index (upper bound) of msked var at each dim
    2612    INTEGER(iwp), DIMENSION(:),   ALLOCATABLE ::  bounds_start_new  !< start index (lower bound) of msked var at each dim
    2613    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  masked_indices    !< dummy list holding all masked indices along a dimension
     2632   INTEGER(iwp), DIMENSION(:),   INTENT(IN)  ::  bounds_end             !< end index per dimension of variable
     2633   INTEGER(iwp), DIMENSION(:),   INTENT(IN)  ::  bounds_start           !< start index per dimension of variable
     2634   INTEGER(iwp), DIMENSION(:),   ALLOCATABLE ::  bounds_origin          !< first index of each dimension
     2635   INTEGER(iwp), DIMENSION(:),   ALLOCATABLE ::  bounds_start_internal  !< start index per dim. for output after masking
     2636   INTEGER(iwp), DIMENSION(:),   ALLOCATABLE ::  value_counts           !< count of indices to be written per dimension
     2637   INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  masked_indices         !< list containing all output indices along a dimension
    26142638
    26152639   LOGICAL ::  do_output  !< true if any data lies within given range of masked dimension
     
    27452769
    27462770      !-- Save starting index (lower bounds) of each dimension
    2747       ALLOCATE( bounds_dim_start(SIZE( dimension_list )) )
    2748       DO  d = 1, SIZE( dimension_list )
    2749          bounds_dim_start(d) = dimension_list(d)%bounds(1)
    2750       ENDDO
    2751 
    2752       ALLOCATE( bounds_start_new(SIZE( dimension_list )) )
    2753       ALLOCATE( bounds_end_new(SIZE( dimension_list ))   )
     2771      ALLOCATE( bounds_origin(SIZE( dimension_list )) )
     2772      ALLOCATE( bounds_start_internal(SIZE( dimension_list )) )
     2773      ALLOCATE( value_counts(SIZE( dimension_list )) )
    27542774
    27552775      WRITE( temp_string, * ) bounds_start
     
    27652785
    27662786      !-- Get bounds for masking
    2767       CALL get_masked_indices_and_masked_dimension_bounds( dimension_list, &
    2768               bounds_start, bounds_end, bounds_start_new, bounds_end_new,  &
    2769               masked_indices, do_output )
    2770 
    2771       WRITE( temp_string, * ) bounds_start_new
     2787      CALL get_masked_indices_and_masked_dimension_bounds( dimension_list,                  &
     2788              bounds_start, bounds_end, bounds_start_internal, value_counts, bounds_origin, &
     2789              masked_indices )
     2790
     2791      do_output = .NOT. ANY( value_counts == 0 )
     2792
     2793      WRITE( temp_string, * ) bounds_start_internal
    27722794      CALL internal_message( 'debug', routine_name //                     &
    27732795                                      ': file "' // TRIM( filename ) //   &
    27742796                                       '": variable "' // TRIM( name ) // &
    2775                                        '": bounds_start_new =' // TRIM( temp_string ) )
    2776       WRITE( temp_string, * ) bounds_end_new
     2797                                       '": bounds_start_internal =' // TRIM( temp_string ) )
     2798      WRITE( temp_string, * ) value_counts
    27772799      CALL internal_message( 'debug', routine_name //                     &
    27782800                                      ': file "' // TRIM( filename ) //   &
    27792801                                       '": variable "' // TRIM( name ) // &
    2780                                        '": bounds_end_new =' // TRIM( temp_string ) )
     2802                                       '": value_counts =' // TRIM( temp_string ) )
    27812803
    27822804      !-- Mask and resort variable
     
    27862808      ELSEIF ( PRESENT( var_int8_1d ) )  THEN
    27872809         IF ( do_output ) THEN
    2788             ALLOCATE( var_int8_1d_resorted(bounds_start_new(1):bounds_end_new(1)) )
     2810            ALLOCATE( var_int8_1d_resorted(0:value_counts(1)-1) )
    27892811            !$OMP PARALLEL PRIVATE (i)
    27902812            !$OMP DO
    2791             DO  i = bounds_start_new(1), bounds_end_new(1)
     2813            DO  i = 0, value_counts(1) - 1
    27922814               var_int8_1d_resorted(i) = var_int8_1d(masked_indices(1,i))
    27932815            ENDDO
     
    28002822      ELSEIF ( PRESENT( var_int8_2d ) )  THEN
    28012823         IF ( do_output ) THEN
    2802             ALLOCATE( var_int8_2d_resorted(bounds_start_new(1):bounds_end_new(1), &
    2803                                            bounds_start_new(2):bounds_end_new(2)) )
     2824            ALLOCATE( var_int8_2d_resorted(0:value_counts(1)-1, &
     2825                                           0:value_counts(2)-1) )
    28042826            !$OMP PARALLEL PRIVATE (i,j)
    28052827            !$OMP DO
    2806             DO  i = bounds_start_new(1), bounds_end_new(1)
    2807                DO  j = bounds_start_new(2), bounds_end_new(2)
     2828            DO  i = 0, value_counts(1) - 1
     2829               DO  j = 0, value_counts(2) - 1
    28082830                  var_int8_2d_resorted(i,j) = var_int8_2d(masked_indices(2,j), &
    28092831                                                          masked_indices(1,i)  )
     
    28182840      ELSEIF ( PRESENT( var_int8_3d ) )  THEN
    28192841         IF ( do_output ) THEN
    2820             ALLOCATE( var_int8_3d_resorted(bounds_start_new(1):bounds_end_new(1), &
    2821                                            bounds_start_new(2):bounds_end_new(2), &
    2822                                            bounds_start_new(3):bounds_end_new(3)) )
     2842            ALLOCATE( var_int8_3d_resorted(0:value_counts(1)-1, &
     2843                                           0:value_counts(2)-1, &
     2844                                           0:value_counts(3)-1) )
    28232845            !$OMP PARALLEL PRIVATE (i,j,k)
    28242846            !$OMP DO
    2825             DO  i = bounds_start_new(1), bounds_end_new(1)
    2826                DO  j = bounds_start_new(2), bounds_end_new(2)
    2827                   DO  k = bounds_start_new(3), bounds_end_new(3)
     2847            DO  i = 0, value_counts(1) - 1
     2848               DO  j = 0, value_counts(2) - 1
     2849                  DO  k = 0, value_counts(3) - 1
    28282850                     var_int8_3d_resorted(i,j,k) = var_int8_3d(masked_indices(3,k), &
    28292851                                                               masked_indices(2,j), &
     
    28442866      ELSEIF ( PRESENT( var_int16_1d ) )  THEN
    28452867         IF ( do_output ) THEN
    2846             ALLOCATE( var_int16_1d_resorted(bounds_start_new(1):bounds_end_new(1)) )
     2868            ALLOCATE( var_int16_1d_resorted(0:value_counts(1)-1) )
    28472869            !$OMP PARALLEL PRIVATE (i)
    28482870            !$OMP DO
    2849             DO  i = bounds_start_new(1), bounds_end_new(1)
     2871            DO  i = 0, value_counts(1) - 1
    28502872               var_int16_1d_resorted(i) = var_int16_1d(masked_indices(1,i))
    28512873            ENDDO
     
    28582880      ELSEIF ( PRESENT( var_int16_2d ) )  THEN
    28592881         IF ( do_output ) THEN
    2860             ALLOCATE( var_int16_2d_resorted(bounds_start_new(1):bounds_end_new(1), &
    2861                                             bounds_start_new(2):bounds_end_new(2)) )
     2882            ALLOCATE( var_int16_2d_resorted(0:value_counts(1)-1, &
     2883                                            0:value_counts(2)-1) )
    28622884            !$OMP PARALLEL PRIVATE (i,j)
    28632885            !$OMP DO
    2864             DO  i = bounds_start_new(1), bounds_end_new(1)
    2865                DO  j = bounds_start_new(2), bounds_end_new(2)
     2886            DO  i = 0, value_counts(1) - 1
     2887               DO  j = 0, value_counts(2) - 1
    28662888                  var_int16_2d_resorted(i,j) = var_int16_2d(masked_indices(2,j), &
    28672889                                                            masked_indices(1,i))
     
    28762898      ELSEIF ( PRESENT( var_int16_3d ) )  THEN
    28772899         IF ( do_output ) THEN
    2878             ALLOCATE( var_int16_3d_resorted(bounds_start_new(1):bounds_end_new(1), &
    2879                                             bounds_start_new(2):bounds_end_new(2), &
    2880                                             bounds_start_new(3):bounds_end_new(3)) )
     2900            ALLOCATE( var_int16_3d_resorted(0:value_counts(1)-1, &
     2901                                            0:value_counts(2)-1, &
     2902                                            0:value_counts(3)-1) )
    28812903            !$OMP PARALLEL PRIVATE (i,j,k)
    28822904            !$OMP DO
    2883             DO  i = bounds_start_new(1), bounds_end_new(1)
    2884                DO  j = bounds_start_new(2), bounds_end_new(2)
    2885                   DO  k = bounds_start_new(3), bounds_end_new(3)
     2905            DO  i = 0, value_counts(1) - 1
     2906               DO  j = 0, value_counts(2) - 1
     2907                  DO  k = 0, value_counts(3) - 1
    28862908                     var_int16_3d_resorted(i,j,k) = var_int16_3d(masked_indices(3,k), &
    28872909                                                                 masked_indices(2,j), &
     
    29022924      ELSEIF ( PRESENT( var_int32_1d ) )  THEN
    29032925         IF ( do_output ) THEN
    2904             ALLOCATE( var_int32_1d_resorted(bounds_start_new(1):bounds_end_new(1)) )
     2926            ALLOCATE( var_int32_1d_resorted(0:value_counts(1)-1) )
    29052927            !$OMP PARALLEL PRIVATE (i)
    29062928            !$OMP DO
    2907             DO  i = bounds_start_new(1), bounds_end_new(1)
     2929            DO  i = 0, value_counts(1) - 1
    29082930               var_int32_1d_resorted(i) = var_int32_1d(masked_indices(1,i))
    29092931            ENDDO
     
    29162938      ELSEIF ( PRESENT( var_int32_2d ) )  THEN
    29172939         IF ( do_output ) THEN
    2918             ALLOCATE( var_int32_2d_resorted(bounds_start_new(1):bounds_end_new(1), &
    2919                                             bounds_start_new(2):bounds_end_new(2)) )
     2940            ALLOCATE( var_int32_2d_resorted(0:value_counts(1)-1, &
     2941                                            0:value_counts(2)-1) )
    29202942            !$OMP PARALLEL PRIVATE (i,j)
    29212943            !$OMP DO
    2922             DO  i = bounds_start_new(1), bounds_end_new(1)
    2923                DO  j = bounds_start_new(2), bounds_end_new(2)
     2944            DO  i = 0, value_counts(1) - 1
     2945               DO  j = 0, value_counts(2) - 1
    29242946                  var_int32_2d_resorted(i,j) = var_int32_2d(masked_indices(2,j), &
    29252947                                                            masked_indices(1,i)  )
     
    29342956      ELSEIF ( PRESENT( var_int32_3d ) )  THEN
    29352957         IF ( do_output ) THEN
    2936             ALLOCATE( var_int32_3d_resorted(bounds_start_new(1):bounds_end_new(1), &
    2937                                             bounds_start_new(2):bounds_end_new(2), &
    2938                                             bounds_start_new(3):bounds_end_new(3)) )
     2958            ALLOCATE( var_int32_3d_resorted(0:value_counts(1)-1, &
     2959                                            0:value_counts(2)-1, &
     2960                                            0:value_counts(3)-1) )
    29392961            !$OMP PARALLEL PRIVATE (i,j,k)
    29402962            !$OMP DO
    2941             DO  i = bounds_start_new(1), bounds_end_new(1)
    2942                DO  j = bounds_start_new(2), bounds_end_new(2)
    2943                   DO  k = bounds_start_new(3), bounds_end_new(3)
     2963            DO  i = 0, value_counts(1) - 1
     2964               DO  j = 0, value_counts(2) - 1
     2965                  DO  k = 0, value_counts(3) - 1
    29442966                     var_int32_3d_resorted(i,j,k) = var_int32_3d(masked_indices(3,k), &
    29452967                                                                 masked_indices(2,j), &
     
    29602982      ELSEIF ( PRESENT( var_intwp_1d ) )  THEN
    29612983         IF ( do_output ) THEN
    2962             ALLOCATE( var_intwp_1d_resorted(bounds_start_new(1):bounds_end_new(1)) )
     2984            ALLOCATE( var_intwp_1d_resorted(0:value_counts(1)-1) )
    29632985            !$OMP PARALLEL PRIVATE (i)
    29642986            !$OMP DO
    2965             DO  i = bounds_start_new(1), bounds_end_new(1)
     2987            DO  i = 0, value_counts(1) - 1
    29662988               var_intwp_1d_resorted(i) = var_intwp_1d(masked_indices(1,i))
    29672989            ENDDO
     
    29742996      ELSEIF ( PRESENT( var_intwp_2d ) )  THEN
    29752997         IF ( do_output ) THEN
    2976             ALLOCATE( var_intwp_2d_resorted(bounds_start_new(1):bounds_end_new(1), &
    2977                                             bounds_start_new(2):bounds_end_new(2)) )
     2998            ALLOCATE( var_intwp_2d_resorted(0:value_counts(1)-1, &
     2999                                            0:value_counts(2)-1) )
    29783000            !$OMP PARALLEL PRIVATE (i,j)
    29793001            !$OMP DO
    2980             DO  i = bounds_start_new(1), bounds_end_new(1)
    2981                DO  j = bounds_start_new(2), bounds_end_new(2)
     3002            DO  i = 0, value_counts(1) - 1
     3003               DO  j = 0, value_counts(2) - 1
    29823004                  var_intwp_2d_resorted(i,j) = var_intwp_2d(masked_indices(2,j), &
    29833005                                                            masked_indices(1,i)  )
     
    29923014      ELSEIF ( PRESENT( var_intwp_3d ) )  THEN
    29933015         IF ( do_output ) THEN
    2994             ALLOCATE( var_intwp_3d_resorted(bounds_start_new(1):bounds_end_new(1), &
    2995                                             bounds_start_new(2):bounds_end_new(2), &
    2996                                             bounds_start_new(3):bounds_end_new(3)) )
     3016            ALLOCATE( var_intwp_3d_resorted(0:value_counts(1)-1, &
     3017                                            0:value_counts(2)-1, &
     3018                                            0:value_counts(3)-1) )
    29973019            !$OMP PARALLEL PRIVATE (i,j,k)
    29983020            !$OMP DO
    2999             DO  i = bounds_start_new(1), bounds_end_new(1)
    3000                DO  j = bounds_start_new(2), bounds_end_new(2)
    3001                   DO  k = bounds_start_new(3), bounds_end_new(3)
     3021            DO  i = 0, value_counts(1) - 1
     3022               DO  j = 0, value_counts(2) - 1
     3023                  DO  k = 0, value_counts(3) - 1
    30023024                     var_intwp_3d_resorted(i,j,k) = var_intwp_3d(masked_indices(3,k), &
    30033025                                                                 masked_indices(2,j), &
     
    30183040      ELSEIF ( PRESENT( var_real32_1d ) )  THEN
    30193041         IF ( do_output ) THEN
    3020             ALLOCATE( var_real32_1d_resorted(bounds_start_new(1):bounds_end_new(1)) )
     3042            ALLOCATE( var_real32_1d_resorted(0:value_counts(1)-1) )
    30213043            !$OMP PARALLEL PRIVATE (i)
    30223044            !$OMP DO
    3023             DO  i = bounds_start_new(1), bounds_end_new(1)
     3045            DO  i = 0, value_counts(1) - 1
    30243046               var_real32_1d_resorted(i) = var_real32_1d(masked_indices(1,i))
    30253047            ENDDO
     
    30323054      ELSEIF ( PRESENT( var_real32_2d ) )  THEN
    30333055         IF ( do_output ) THEN
    3034             ALLOCATE( var_real32_2d_resorted(bounds_start_new(1):bounds_end_new(1), &
    3035                                              bounds_start_new(2):bounds_end_new(2)) )
     3056            ALLOCATE( var_real32_2d_resorted(0:value_counts(1)-1, &
     3057                                             0:value_counts(2)-1) )
    30363058            !$OMP PARALLEL PRIVATE (i,j)
    30373059            !$OMP DO
    3038             DO  i = bounds_start_new(1), bounds_end_new(1)
    3039                DO  j = bounds_start_new(2), bounds_end_new(2)
     3060            DO  i = 0, value_counts(1) - 1
     3061               DO  j = 0, value_counts(2) - 1
    30403062                  var_real32_2d_resorted(i,j) = var_real32_2d(masked_indices(2,j), &
    30413063                                                              masked_indices(1,i)  )
     
    30503072      ELSEIF ( PRESENT( var_real32_3d ) )  THEN
    30513073         IF ( do_output ) THEN
    3052             ALLOCATE( var_real32_3d_resorted(bounds_start_new(1):bounds_end_new(1), &
    3053                                              bounds_start_new(2):bounds_end_new(2), &
    3054                                              bounds_start_new(3):bounds_end_new(3)) )
     3074            ALLOCATE( var_real32_3d_resorted(0:value_counts(1)-1, &
     3075                                             0:value_counts(2)-1, &
     3076                                             0:value_counts(3)-1) )
    30553077            !$OMP PARALLEL PRIVATE (i,j,k)
    30563078            !$OMP DO
    3057             DO  i = bounds_start_new(1), bounds_end_new(1)
    3058                DO  j = bounds_start_new(2), bounds_end_new(2)
    3059                   DO  k = bounds_start_new(3), bounds_end_new(3)
     3079            DO  i = 0, value_counts(1) - 1
     3080               DO  j = 0, value_counts(2) - 1
     3081                  DO  k = 0, value_counts(3) - 1
    30603082                     var_real32_3d_resorted(i,j,k) = var_real32_3d(masked_indices(3,k), &
    30613083                                                                   masked_indices(2,j), &
     
    30763098      ELSEIF ( PRESENT( var_real64_1d ) )  THEN
    30773099         IF ( do_output ) THEN
    3078             ALLOCATE( var_real64_1d_resorted(bounds_start_new(1):bounds_end_new(1)) )
     3100            ALLOCATE( var_real64_1d_resorted(0:value_counts(1)-1) )
    30793101            !$OMP PARALLEL PRIVATE (i)
    30803102            !$OMP DO
    3081             DO  i = bounds_start_new(1), bounds_end_new(1)
     3103            DO  i = 0, value_counts(1) - 1
    30823104               var_real64_1d_resorted(i) = var_real64_1d(masked_indices(1,i))
    30833105            ENDDO
     
    30903112      ELSEIF ( PRESENT( var_real64_2d ) )  THEN
    30913113         IF ( do_output ) THEN
    3092             ALLOCATE( var_real64_2d_resorted(bounds_start_new(1):bounds_end_new(1), &
    3093                                              bounds_start_new(2):bounds_end_new(2)) )
     3114            ALLOCATE( var_real64_2d_resorted(0:value_counts(1)-1, &
     3115                                             0:value_counts(2)-1) )
    30943116            !$OMP PARALLEL PRIVATE (i,j)
    30953117            !$OMP DO
    3096             DO  i = bounds_start_new(1), bounds_end_new(1)
    3097                DO  j = bounds_start_new(2), bounds_end_new(2)
     3118            DO  i = 0, value_counts(1) - 1
     3119               DO  j = 0, value_counts(2) - 1
    30983120                  var_real64_2d_resorted(i,j) = var_real64_2d(masked_indices(2,j), &
    30993121                                                              masked_indices(1,i)  )
     
    31083130      ELSEIF ( PRESENT( var_real64_3d ) )  THEN
    31093131         IF ( do_output ) THEN
    3110             ALLOCATE( var_real64_3d_resorted(bounds_start_new(1):bounds_end_new(1), &
    3111                                              bounds_start_new(2):bounds_end_new(2), &
    3112                                              bounds_start_new(3):bounds_end_new(3)) )
     3132            ALLOCATE( var_real64_3d_resorted(0:value_counts(1)-1, &
     3133                                             0:value_counts(2)-1, &
     3134                                             0:value_counts(3)-1) )
    31133135            !$OMP PARALLEL PRIVATE (i,j,k)
    31143136            !$OMP DO
    3115             DO  i = bounds_start_new(1), bounds_end_new(1)
    3116                DO  j = bounds_start_new(2), bounds_end_new(2)
    3117                   DO  k = bounds_start_new(3), bounds_end_new(3)
     3137            DO  i = 0, value_counts(1) - 1
     3138               DO  j = 0, value_counts(2) - 1
     3139                  DO  k = 0, value_counts(3) - 1
    31183140                     var_real64_3d_resorted(i,j,k) = var_real64_3d(masked_indices(3,k), &
    31193141                                                                   masked_indices(2,j), &
     
    31343156      ELSEIF ( PRESENT( var_realwp_1d ) )  THEN
    31353157         IF ( do_output ) THEN
    3136             ALLOCATE( var_realwp_1d_resorted(bounds_start_new(1):bounds_end_new(1)) )
     3158            ALLOCATE( var_realwp_1d_resorted(0:value_counts(1)-1) )
    31373159            !$OMP PARALLEL PRIVATE (i)
    31383160            !$OMP DO
    3139             DO  i = bounds_start_new(1), bounds_end_new(1)
     3161            DO  i = 0, value_counts(1) - 1
    31403162               var_realwp_1d_resorted(i) = var_realwp_1d(masked_indices(1,i))
    31413163            ENDDO
     
    31483170      ELSEIF ( PRESENT( var_realwp_2d ) )  THEN
    31493171         IF ( do_output ) THEN
    3150             ALLOCATE( var_realwp_2d_resorted(bounds_start_new(1):bounds_end_new(1), &
    3151                                              bounds_start_new(2):bounds_end_new(2)) )
     3172            ALLOCATE( var_realwp_2d_resorted(0:value_counts(1)-1, &
     3173                                             0:value_counts(2)-1) )
    31523174            !$OMP PARALLEL PRIVATE (i,j)
    31533175            !$OMP DO
    3154             DO  i = bounds_start_new(1), bounds_end_new(1)
    3155                DO  j = bounds_start_new(2), bounds_end_new(2)
     3176            DO  i = 0, value_counts(1) - 1
     3177               DO  j = 0, value_counts(2) - 1
    31563178                  var_realwp_2d_resorted(i,j) = var_realwp_2d(masked_indices(2,j), &
    31573179                                                              masked_indices(1,i)  )
     
    31663188      ELSEIF ( PRESENT( var_realwp_3d ) )  THEN
    31673189         IF ( do_output ) THEN
    3168             ALLOCATE( var_realwp_3d_resorted(bounds_start_new(1):bounds_end_new(1), &
    3169                                              bounds_start_new(2):bounds_end_new(2), &
    3170                                              bounds_start_new(3):bounds_end_new(3)) )
     3190            ALLOCATE( var_realwp_3d_resorted(0:value_counts(1)-1, &
     3191                                             0:value_counts(2)-1, &
     3192                                             0:value_counts(3)-1) )
    31713193            !$OMP PARALLEL PRIVATE (i,j,k)
    31723194            !$OMP DO
    3173             DO  i = bounds_start_new(1), bounds_end_new(1)
    3174                DO  j = bounds_start_new(2), bounds_end_new(2)
    3175                   DO  k = bounds_start_new(3), bounds_end_new(3)
     3195            DO  i = 0, value_counts(1) - 1
     3196               DO  j = 0, value_counts(2) - 1
     3197                  DO  k = 0, value_counts(3) - 1
    31763198                     var_realwp_3d_resorted(i,j,k) = var_realwp_3d(masked_indices(3,k), &
    31773199                                                                   masked_indices(2,j), &
     
    32073229            !-- 8bit integer output
    32083230            IF ( PRESENT( var_int8_0d ) )  THEN
    3209                CALL binary_write_variable( file_id, var_id,                                      &
    3210                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3231               CALL binary_write_variable( file_id, var_id,                           &
     3232                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32113233                       var_int8_0d=var_int8_0d_pointer, return_value=output_return_value )
    32123234            ELSEIF ( PRESENT( var_int8_1d ) )  THEN
    3213                CALL binary_write_variable( file_id, var_id,                                      &
    3214                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3235               CALL binary_write_variable( file_id, var_id,                           &
     3236                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32153237                       var_int8_1d=var_int8_1d_pointer, return_value=output_return_value )
    32163238            ELSEIF ( PRESENT( var_int8_2d ) )  THEN
    3217                CALL binary_write_variable( file_id, var_id,                                      &
    3218                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3239               CALL binary_write_variable( file_id, var_id,                           &
     3240                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32193241                       var_int8_2d=var_int8_2d_pointer, return_value=output_return_value )
    32203242            ELSEIF ( PRESENT( var_int8_3d ) )  THEN
    3221                CALL binary_write_variable( file_id, var_id,                                      &
    3222                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3243               CALL binary_write_variable( file_id, var_id,                           &
     3244                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32233245                       var_int8_3d=var_int8_3d_pointer, return_value=output_return_value )
    32243246            !-- 16bit integer output
    32253247            ELSEIF ( PRESENT( var_int16_0d ) )  THEN
    3226                CALL binary_write_variable( file_id, var_id,                                      &
    3227                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3248               CALL binary_write_variable( file_id, var_id,                           &
     3249                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32283250                       var_int16_0d=var_int16_0d_pointer, return_value=output_return_value )
    32293251            ELSEIF ( PRESENT( var_int16_1d ) )  THEN
    3230                CALL binary_write_variable( file_id, var_id,                                      &
    3231                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3252               CALL binary_write_variable( file_id, var_id,                           &
     3253                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32323254                       var_int16_1d=var_int16_1d_pointer, return_value=output_return_value )
    32333255            ELSEIF ( PRESENT( var_int16_2d ) )  THEN
    3234                CALL binary_write_variable( file_id, var_id,                                      &
    3235                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3256               CALL binary_write_variable( file_id, var_id,                           &
     3257                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32363258                       var_int16_2d=var_int16_2d_pointer, return_value=output_return_value )
    32373259            ELSEIF ( PRESENT( var_int16_3d ) )  THEN
    3238                CALL binary_write_variable( file_id, var_id,                                      &
    3239                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3260               CALL binary_write_variable( file_id, var_id,                           &
     3261                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32403262                       var_int16_3d=var_int16_3d_pointer, return_value=output_return_value )
    32413263            !-- 32bit integer output
    32423264            ELSEIF ( PRESENT( var_int32_0d ) )  THEN
    3243                CALL binary_write_variable( file_id, var_id,                                      &
    3244                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3265               CALL binary_write_variable( file_id, var_id,                           &
     3266                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32453267                       var_int32_0d=var_int32_0d_pointer, return_value=output_return_value )
    32463268            ELSEIF ( PRESENT( var_int32_1d ) )  THEN
    3247                CALL binary_write_variable( file_id, var_id,                                      &
    3248                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3269               CALL binary_write_variable( file_id, var_id,                           &
     3270                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32493271                       var_int32_1d=var_int32_1d_pointer, return_value=output_return_value )
    32503272            ELSEIF ( PRESENT( var_int32_2d ) )  THEN
    3251                CALL binary_write_variable( file_id, var_id,                                      &
    3252                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3273               CALL binary_write_variable( file_id, var_id,                           &
     3274                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32533275                       var_int32_2d=var_int32_2d_pointer, return_value=output_return_value )
    32543276            ELSEIF ( PRESENT( var_int32_3d ) )  THEN
    3255                CALL binary_write_variable( file_id, var_id,                                      &
    3256                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3277               CALL binary_write_variable( file_id, var_id,                           &
     3278                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32573279                       var_int32_3d=var_int32_3d_pointer, return_value=output_return_value )
    32583280            !-- working-precision integer output
    32593281            ELSEIF ( PRESENT( var_intwp_0d ) )  THEN
    3260                CALL binary_write_variable( file_id, var_id,                                      &
    3261                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3282               CALL binary_write_variable( file_id, var_id,                           &
     3283                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32623284                       var_intwp_0d=var_intwp_0d_pointer, return_value=output_return_value )
    32633285            ELSEIF ( PRESENT( var_intwp_1d ) )  THEN
    3264                CALL binary_write_variable( file_id, var_id,                                      &
    3265                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3286               CALL binary_write_variable( file_id, var_id,                           &
     3287                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32663288                       var_intwp_1d=var_intwp_1d_pointer, return_value=output_return_value )
    32673289            ELSEIF ( PRESENT( var_intwp_2d ) )  THEN
    3268                CALL binary_write_variable( file_id, var_id,                                      &
    3269                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3290               CALL binary_write_variable( file_id, var_id,                           &
     3291                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32703292                       var_intwp_2d=var_intwp_2d_pointer, return_value=output_return_value )
    32713293            ELSEIF ( PRESENT( var_intwp_3d ) )  THEN
    3272                CALL binary_write_variable( file_id, var_id,                                      &
    3273                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3294               CALL binary_write_variable( file_id, var_id,                           &
     3295                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32743296                       var_intwp_3d=var_intwp_3d_pointer, return_value=output_return_value )
    32753297            !-- 32bit real output
    32763298            ELSEIF ( PRESENT( var_real32_0d ) )  THEN
    3277                CALL binary_write_variable( file_id, var_id,                                      &
    3278                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3299               CALL binary_write_variable( file_id, var_id,                           &
     3300                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32793301                       var_real32_0d=var_real32_0d_pointer, return_value=output_return_value )
    32803302            ELSEIF ( PRESENT( var_real32_1d ) )  THEN
    3281                CALL binary_write_variable( file_id, var_id,                                      &
    3282                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3303               CALL binary_write_variable( file_id, var_id,                           &
     3304                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32833305                       var_real32_1d=var_real32_1d_pointer, return_value=output_return_value )
    32843306            ELSEIF ( PRESENT( var_real32_2d ) )  THEN
    3285                CALL binary_write_variable( file_id, var_id,                                      &
    3286                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3307               CALL binary_write_variable( file_id, var_id,                           &
     3308                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32873309                       var_real32_2d=var_real32_2d_pointer, return_value=output_return_value )
    32883310            ELSEIF ( PRESENT( var_real32_3d ) )  THEN
    3289                CALL binary_write_variable( file_id, var_id,                                      &
    3290                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3311               CALL binary_write_variable( file_id, var_id,                           &
     3312                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32913313                       var_real32_3d=var_real32_3d_pointer, return_value=output_return_value )
    32923314            !-- 64bit real output
    32933315            ELSEIF ( PRESENT( var_real64_0d ) )  THEN
    3294                CALL binary_write_variable( file_id, var_id,                                      &
    3295                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3316               CALL binary_write_variable( file_id, var_id,                           &
     3317                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    32963318                       var_real64_0d=var_real64_0d_pointer, return_value=output_return_value )
    32973319            ELSEIF ( PRESENT( var_real64_1d ) )  THEN
    3298                CALL binary_write_variable( file_id, var_id,                                      &
    3299                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3320               CALL binary_write_variable( file_id, var_id,                           &
     3321                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33003322                       var_real64_1d=var_real64_1d_pointer, return_value=output_return_value )
    33013323            ELSEIF ( PRESENT( var_real64_2d ) )  THEN
    3302                CALL binary_write_variable( file_id, var_id,                                      &
    3303                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3324               CALL binary_write_variable( file_id, var_id,                           &
     3325                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33043326                       var_real64_2d=var_real64_2d_pointer, return_value=output_return_value )
    33053327            ELSEIF ( PRESENT( var_real64_3d ) )  THEN
    3306                CALL binary_write_variable( file_id, var_id,                                      &
    3307                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3328               CALL binary_write_variable( file_id, var_id,                           &
     3329                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33083330                       var_real64_3d=var_real64_3d_pointer, return_value=output_return_value )
    33093331            !-- working-precision real output
    33103332            ELSEIF ( PRESENT( var_realwp_0d ) )  THEN
    3311                CALL binary_write_variable( file_id, var_id,                                      &
    3312                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3333               CALL binary_write_variable( file_id, var_id,                           &
     3334                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33133335                       var_realwp_0d=var_realwp_0d_pointer, return_value=output_return_value )
    33143336            ELSEIF ( PRESENT( var_realwp_1d ) )  THEN
    3315                CALL binary_write_variable( file_id, var_id,                                      &
    3316                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3337               CALL binary_write_variable( file_id, var_id,                           &
     3338                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33173339                       var_realwp_1d=var_realwp_1d_pointer, return_value=output_return_value )
    33183340            ELSEIF ( PRESENT( var_realwp_2d ) )  THEN
    3319                CALL binary_write_variable( file_id, var_id,                                      &
    3320                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3341               CALL binary_write_variable( file_id, var_id,                           &
     3342                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33213343                       var_realwp_2d=var_realwp_2d_pointer, return_value=output_return_value )
    33223344            ELSEIF ( PRESENT( var_realwp_3d ) )  THEN
    3323                CALL binary_write_variable( file_id, var_id,                                      &
    3324                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3345               CALL binary_write_variable( file_id, var_id,                           &
     3346                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33253347                       var_realwp_3d=var_realwp_3d_pointer, return_value=output_return_value )
    33263348            ELSE
     
    33363358            !-- 8bit integer output
    33373359            IF ( PRESENT( var_int8_0d ) )  THEN
    3338                CALL netcdf4_write_variable( file_id, var_id,                              &
    3339                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3360               CALL netcdf4_write_variable( file_id, var_id,                          &
     3361                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33403362                       var_int8_0d=var_int8_0d_pointer, return_value=output_return_value )
    33413363            ELSEIF ( PRESENT( var_int8_1d ) )  THEN
    3342                CALL netcdf4_write_variable( file_id, var_id,                              &
    3343                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3364               CALL netcdf4_write_variable( file_id, var_id,                          &
     3365                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33443366                       var_int8_1d=var_int8_1d_pointer, return_value=output_return_value )
    33453367            ELSEIF ( PRESENT( var_int8_2d ) )  THEN
    3346                CALL netcdf4_write_variable( file_id, var_id,                              &
    3347                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3368               CALL netcdf4_write_variable( file_id, var_id,                          &
     3369                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33483370                       var_int8_2d=var_int8_2d_pointer, return_value=output_return_value )
    33493371            ELSEIF ( PRESENT( var_int8_3d ) )  THEN
    3350                CALL netcdf4_write_variable( file_id, var_id,                              &
    3351                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3372               CALL netcdf4_write_variable( file_id, var_id,                          &
     3373                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33523374                       var_int8_3d=var_int8_3d_pointer, return_value=output_return_value )
    33533375            !-- 16bit integer output
    33543376            ELSEIF ( PRESENT( var_int16_0d ) )  THEN
    3355                CALL netcdf4_write_variable( file_id, var_id,                              &
    3356                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3377               CALL netcdf4_write_variable( file_id, var_id,                          &
     3378                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33573379                       var_int16_0d=var_int16_0d_pointer, return_value=output_return_value )
    33583380            ELSEIF ( PRESENT( var_int16_1d ) )  THEN
    3359                CALL netcdf4_write_variable( file_id, var_id,                              &
    3360                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3381               CALL netcdf4_write_variable( file_id, var_id,                          &
     3382                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33613383                       var_int16_1d=var_int16_1d_pointer, return_value=output_return_value )
    33623384            ELSEIF ( PRESENT( var_int16_2d ) )  THEN
    3363                CALL netcdf4_write_variable( file_id, var_id,                              &
    3364                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3385               CALL netcdf4_write_variable( file_id, var_id,                          &
     3386                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33653387                       var_int16_2d=var_int16_2d_pointer, return_value=output_return_value )
    33663388            ELSEIF ( PRESENT( var_int16_3d ) )  THEN
    3367                CALL netcdf4_write_variable( file_id, var_id,                              &
    3368                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3389               CALL netcdf4_write_variable( file_id, var_id,                          &
     3390                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33693391                       var_int16_3d=var_int16_3d_pointer, return_value=output_return_value )
    33703392            !-- 32bit integer output
    33713393            ELSEIF ( PRESENT( var_int32_0d ) )  THEN
    3372                CALL netcdf4_write_variable( file_id, var_id,                              &
    3373                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3394               CALL netcdf4_write_variable( file_id, var_id,                          &
     3395                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33743396                       var_int32_0d=var_int32_0d_pointer, return_value=output_return_value )
    33753397            ELSEIF ( PRESENT( var_int32_1d ) )  THEN
    3376                CALL netcdf4_write_variable( file_id, var_id,                              &
    3377                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3398               CALL netcdf4_write_variable( file_id, var_id,                          &
     3399                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33783400                       var_int32_1d=var_int32_1d_pointer, return_value=output_return_value )
    33793401            ELSEIF ( PRESENT( var_int32_2d ) )  THEN
    3380                CALL netcdf4_write_variable( file_id, var_id,                              &
    3381                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3402               CALL netcdf4_write_variable( file_id, var_id,                          &
     3403                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33823404                       var_int32_2d=var_int32_2d_pointer, return_value=output_return_value )
    33833405            ELSEIF ( PRESENT( var_int32_3d ) )  THEN
    3384                CALL netcdf4_write_variable( file_id, var_id,                              &
    3385                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3406               CALL netcdf4_write_variable( file_id, var_id,                          &
     3407                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33863408                       var_int32_3d=var_int32_3d_pointer, return_value=output_return_value )
    33873409            !-- working-precision integer output
    33883410            ELSEIF ( PRESENT( var_intwp_0d ) )  THEN
    3389                CALL netcdf4_write_variable( file_id, var_id,                              &
    3390                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3411               CALL netcdf4_write_variable( file_id, var_id,                          &
     3412                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33913413                       var_intwp_0d=var_intwp_0d_pointer, return_value=output_return_value )
    33923414            ELSEIF ( PRESENT( var_intwp_1d ) )  THEN
    3393                CALL netcdf4_write_variable( file_id, var_id,                              &
    3394                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3415               CALL netcdf4_write_variable( file_id, var_id,                          &
     3416                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33953417                       var_intwp_1d=var_intwp_1d_pointer, return_value=output_return_value )
    33963418            ELSEIF ( PRESENT( var_intwp_2d ) )  THEN
    3397                CALL netcdf4_write_variable( file_id, var_id,                              &
    3398                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3419               CALL netcdf4_write_variable( file_id, var_id,                          &
     3420                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    33993421                       var_intwp_2d=var_intwp_2d_pointer, return_value=output_return_value )
    34003422            ELSEIF ( PRESENT( var_intwp_3d ) )  THEN
    3401                CALL netcdf4_write_variable( file_id, var_id,                              &
    3402                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3423               CALL netcdf4_write_variable( file_id, var_id,                          &
     3424                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34033425                       var_intwp_3d=var_intwp_3d_pointer, return_value=output_return_value )
    34043426            !-- 32bit real output
    34053427            ELSEIF ( PRESENT( var_real32_0d ) )  THEN
    3406                CALL netcdf4_write_variable( file_id, var_id,                              &
    3407                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3428               CALL netcdf4_write_variable( file_id, var_id,                          &
     3429                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34083430                       var_real32_0d=var_real32_0d_pointer, return_value=output_return_value )
    34093431            ELSEIF ( PRESENT( var_real32_1d ) )  THEN
    3410                CALL netcdf4_write_variable( file_id, var_id,                              &
    3411                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3432               CALL netcdf4_write_variable( file_id, var_id,                          &
     3433                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34123434                       var_real32_1d=var_real32_1d_pointer, return_value=output_return_value )
    34133435            ELSEIF ( PRESENT( var_real32_2d ) )  THEN
    3414                CALL netcdf4_write_variable( file_id, var_id,                              &
    3415                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3436               CALL netcdf4_write_variable( file_id, var_id,                          &
     3437                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34163438                       var_real32_2d=var_real32_2d_pointer, return_value=output_return_value )
    34173439            ELSEIF ( PRESENT( var_real32_3d ) )  THEN
    3418                CALL netcdf4_write_variable( file_id, var_id,                              &
    3419                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3440               CALL netcdf4_write_variable( file_id, var_id,                          &
     3441                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34203442                       var_real32_3d=var_real32_3d_pointer, return_value=output_return_value )
    34213443            !-- 64bit real output
    34223444            ELSEIF ( PRESENT( var_real64_0d ) )  THEN
    3423                CALL netcdf4_write_variable( file_id, var_id,                              &
    3424                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3445               CALL netcdf4_write_variable( file_id, var_id,                          &
     3446                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34253447                       var_real64_0d=var_real64_0d_pointer, return_value=output_return_value )
    34263448            ELSEIF ( PRESENT( var_real64_1d ) )  THEN
    3427                CALL netcdf4_write_variable( file_id, var_id,                              &
    3428                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3449               CALL netcdf4_write_variable( file_id, var_id,                          &
     3450                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34293451                       var_real64_1d=var_real64_1d_pointer, return_value=output_return_value )
    34303452            ELSEIF ( PRESENT( var_real64_2d ) )  THEN
    3431                CALL netcdf4_write_variable( file_id, var_id,                              &
    3432                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3453               CALL netcdf4_write_variable( file_id, var_id,                          &
     3454                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34333455                       var_real64_2d=var_real64_2d_pointer, return_value=output_return_value )
    34343456            ELSEIF ( PRESENT( var_real64_3d ) )  THEN
    3435                CALL netcdf4_write_variable( file_id, var_id,                              &
    3436                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3457               CALL netcdf4_write_variable( file_id, var_id,                          &
     3458                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34373459                       var_real64_3d=var_real64_3d_pointer, return_value=output_return_value )
    34383460            !-- working-precision real output
    34393461            ELSEIF ( PRESENT( var_realwp_0d ) )  THEN
    3440                CALL netcdf4_write_variable( file_id, var_id,                              &
    3441                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3462               CALL netcdf4_write_variable( file_id, var_id,                          &
     3463                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34423464                       var_realwp_0d=var_realwp_0d_pointer, return_value=output_return_value )
    34433465            ELSEIF ( PRESENT( var_realwp_1d ) )  THEN
    3444                CALL netcdf4_write_variable( file_id, var_id,                              &
    3445                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3466               CALL netcdf4_write_variable( file_id, var_id,                          &
     3467                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34463468                       var_realwp_1d=var_realwp_1d_pointer, return_value=output_return_value )
    34473469            ELSEIF ( PRESENT( var_realwp_2d ) )  THEN
    3448                CALL netcdf4_write_variable( file_id, var_id,                              &
    3449                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3470               CALL netcdf4_write_variable( file_id, var_id,                          &
     3471                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34503472                       var_realwp_2d=var_realwp_2d_pointer, return_value=output_return_value )
    34513473            ELSEIF ( PRESENT( var_realwp_3d ) )  THEN
    3452                CALL netcdf4_write_variable( file_id, var_id,                              &
    3453                        bounds_start_new, bounds_end_new, bounds_dim_start, do_output, is_global, &
     3474               CALL netcdf4_write_variable( file_id, var_id,                          &
     3475                       bounds_start_internal, value_counts, bounds_origin, is_global, &
    34543476                       var_realwp_3d=var_realwp_3d_pointer, return_value=output_return_value )
    34553477            ELSE
     
    36083630! ------------
    36093631!> Search for masked indices of dimensions within the given bounds ('bounds_start' and
    3610 !> 'bounds_end'). Return the masked indices ('masked_indices') of the dimensions and the bounds of
    3611 !> the masked dimensions containing these indices ('bounds_masked_start' and 'bounds_masked_end').
    3612 !> If no masked indices lie within the given bounds, 'mask_in_bounds' is .FALSE..
    3613 !--------------------------------------------------------------------------------------------------!
    3614 SUBROUTINE get_masked_indices_and_masked_dimension_bounds(                                  &
    3615               dimensions, bounds_start, bounds_end, bounds_masked_start, bounds_masked_end, &
    3616               masked_indices, mask_in_bounds )
     3632!> 'bounds_end'). Return the masked indices ('masked_indices') of the dimensions, the first index
     3633!> of the masked dimensions containing these indices ('bounds_masked_start'), the count of masked
     3634!> indices within given bounds ('value_counts') and the origin index of each dimension
     3635!> ('bounds_origin'). If, for any dimension, no masked index lies within the given bounds, counts,
     3636!> starts and origins are set to zero for all dimensions.
     3637!--------------------------------------------------------------------------------------------------!
     3638SUBROUTINE get_masked_indices_and_masked_dimension_bounds(                             &
     3639              dimensions, bounds_start, bounds_end, bounds_masked_start, value_counts, &
     3640              bounds_origin, masked_indices )
    36173641
    36183642   ! CHARACTER(LEN=*), PARAMETER ::  routine_name = 'get_masked_indices_and_masked_dimension_bounds'  !< name of routine
     
    36233647
    36243648   INTEGER(iwp), DIMENSION(:), INTENT(IN)  ::  bounds_end           !< upper bonuds to be searched in
    3625    INTEGER(iwp), DIMENSION(:), INTENT(OUT) ::  bounds_masked_end    !< upper bounds of masked dimensions within given bounds
    36263649   INTEGER(iwp), DIMENSION(:), INTENT(OUT) ::  bounds_masked_start  !< lower bounds of masked dimensions within given bounds
     3650   INTEGER(iwp), DIMENSION(:), INTENT(OUT) ::  bounds_origin        !< first index of each dimension, 0 if dimension is masked
    36273651   INTEGER(iwp), DIMENSION(:), INTENT(IN)  ::  bounds_start         !< lower bounds to be searched in
     3652   INTEGER(iwp), DIMENSION(:), INTENT(OUT) ::  value_counts         !< count of indices per dimension to be output
    36283653
    36293654   INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, INTENT(OUT) ::  masked_indices  !< masked indices within given bounds
    36303655
    3631    LOGICAL, INTENT(OUT) ::  mask_in_bounds  !< true if any masked indices lie within given bounds
    3632 
    36333656   TYPE(dimension_type), DIMENSION(:), INTENT(IN) ::  dimensions  !< dimensions to be searched for masked indices
    36343657
    36353658
    3636    mask_in_bounds = .TRUE.
    3637    ALLOCATE( masked_indices(SIZE( dimensions ),0:MAXVAL( dimensions(:)%length - 1 )) )
     3659   ALLOCATE( masked_indices(SIZE( dimensions ),0:MAXVAL( bounds_end - bounds_start + 1 )) )
    36383660   masked_indices = -HUGE( 0_iwp )
    36393661
     
    36433665      IF ( dimensions(d)%is_masked )  THEN
    36443666
    3645          bounds_masked_end(d) = HUGE( 0_iwp )
     3667         bounds_origin(d) = 0
     3668
    36463669         bounds_masked_start(d) = -HUGE( 0_iwp )
    36473670
    36483671         !-- Find number of masked values within given variable bounds
    3649          j = 0
     3672         value_counts(d) = 0
    36503673         DO  i = LBOUND( dimensions(d)%masked_indices, DIM=1 ), &
    36513674                 UBOUND( dimensions(d)%masked_indices, DIM=1 )
    36523675
    3653             !-- Is masked position within given bounds?
     3676            !-- Is masked index within given bounds?
    36543677            IF ( dimensions(d)%masked_indices(i) >= bounds_start(d)  .AND.  &
    36553678                 dimensions(d)%masked_indices(i) <= bounds_end(d)           )  THEN
    36563679
    3657                !-- Save masked position
    3658                masked_indices(d,i) = dimensions(d)%masked_indices(i)
    3659                j = j + 1
     3680               !-- Save masked index
     3681               masked_indices(d,value_counts(d)) = dimensions(d)%masked_indices(i)
     3682               value_counts(d) = value_counts(d) + 1
    36603683
    36613684               !-- Save bounds of mask within given bounds
    36623685               IF ( bounds_masked_start(d) == -HUGE( 0_iwp ) )  bounds_masked_start(d) = i
    3663                bounds_masked_end(d) = i
    36643686
    36653687            ENDIF
     
    36673689         ENDDO
    36683690
    3669          !-- Set masked bounds to zero if no masked data lies within bounds
    3670          IF ( j == 0 )  THEN
     3691         !-- Set masked bounds to zero if no masked index lies within bounds
     3692         IF ( value_counts(d) == 0 )  THEN
     3693            bounds_origin(:) = 0
    36713694            bounds_masked_start(:) = 0_iwp
    3672             bounds_masked_end(:) = 0_iwp
    3673             mask_in_bounds = .FALSE.
     3695            value_counts(:) = 0_iwp
    36743696            EXIT
    36753697         ENDIF
     
    36773699      ELSE
    36783700
    3679          !-- If dimension is not masked, tread all data within bounds as masked
     3701         !-- If dimension is not masked, save all indices within bounds for output
     3702         bounds_origin(d) = dimensions(d)%bounds(1)
    36803703         bounds_masked_start(d) = bounds_start(d)
    3681          bounds_masked_end(d) = bounds_end(d)
    3682          DO  i = bounds_masked_start(d), bounds_masked_end(d)
    3683             masked_indices(d,i) = i
     3704         value_counts(d) = bounds_end(d) - bounds_start(d) + 1
     3705
     3706         DO  i = 0, value_counts(d) - 1
     3707            masked_indices(d,i) = bounds_start(d) + i
    36843708         ENDDO
    36853709
  • palm/trunk/SOURCE/data_output_netcdf4_module.f90

    r4107 r4123  
    492492!--------------------------------------------------------------------------------------------------!
    493493SUBROUTINE netcdf4_write_variable(                                        &
    494               file_id, var_id, bounds_start, bounds_end, bounds_origin,  &
    495               do_output, is_global,                                       &
     494              file_id, var_id, bounds_start, value_counts, bounds_origin, &
     495              is_global,                                                  &
    496496              var_int8_0d,   var_int8_1d,   var_int8_2d,   var_int8_3d,   &
    497497              var_int16_0d,  var_int16_1d,  var_int16_2d,  var_int16_3d,  &
     
    514514
    515515   INTEGER(iwp), DIMENSION(:), INTENT(IN)  ::  bounds_origin  !< starting index of each dimension
    516    INTEGER(iwp), DIMENSION(:), INTENT(IN)  ::  bounds_end     !< ending index of variable
    517516   INTEGER(iwp), DIMENSION(:), INTENT(IN)  ::  bounds_start   !< starting index of variable
    518517   INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  dim_ids        !< IDs of dimensions of variable in file
    519518   INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  dim_lengths    !< length of dimensions of variable in file
    520    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  value_count    !< count of values along each dimension to be written
     519   INTEGER(iwp), DIMENSION(:), INTENT(IN)  ::  value_counts   !< count of values along each dimension to be written
    521520
    522521   INTEGER(KIND=1), POINTER, INTENT(IN), OPTIONAL                               ::  var_int8_0d  !< output variable
     
    540539   INTEGER(iwp), POINTER, CONTIGUOUS, INTENT(IN), OPTIONAL, DIMENSION(:,:,:) ::  var_intwp_3d  !< output variable
    541540
    542    LOGICAL, INTENT(IN) ::  do_output  !< if false, set count to 0 and do no output
    543541   LOGICAL, INTENT(IN) ::  is_global  !< true if variable is global (same on all PE)
    544542
     
    578576      ndim = SIZE( bounds_start )
    579577
    580       ALLOCATE( value_count(ndim) )
    581 
    582       IF ( do_output ) THEN
    583          value_count = bounds_end - bounds_start + 1
    584       ELSE
    585          value_count = 0
    586       END IF
    587 
    588578      !-- 8bit integer output
    589579      IF ( PRESENT( var_int8_0d ) )  THEN
    590580         nc_stat = NF90_PUT_VAR( file_id, var_id, (/ var_int8_0d /),       &
    591581                                 start = bounds_start - bounds_origin + 1, &
    592                                  count = value_count )
     582                                 count = value_counts )
    593583      ELSEIF ( PRESENT( var_int8_1d ) )  THEN
    594584         nc_stat = NF90_PUT_VAR( file_id, var_id, var_int8_1d,             &
    595585                                 start = bounds_start - bounds_origin + 1, &
    596                                  count = value_count )
     586                                 count = value_counts )
    597587      ELSEIF ( PRESENT( var_int8_2d ) )  THEN
    598588         nc_stat = NF90_PUT_VAR( file_id, var_id, var_int8_2d,             &
    599589                                 start = bounds_start - bounds_origin + 1, &
    600                                  count = value_count )
     590                                 count = value_counts )
    601591      ELSEIF ( PRESENT( var_int8_3d ) )  THEN
    602592         nc_stat = NF90_PUT_VAR( file_id, var_id, var_int8_3d,             &
    603593                                 start = bounds_start - bounds_origin + 1, &
    604                                  count = value_count )
     594                                 count = value_counts )
    605595      !-- 16bit integer output
    606596      ELSEIF ( PRESENT( var_int16_0d ) )  THEN
    607597         nc_stat = NF90_PUT_VAR( file_id, var_id, (/ var_int16_0d /),      &
    608598                                 start = bounds_start - bounds_origin + 1, &
    609                                  count = value_count )
     599                                 count = value_counts )
    610600      ELSEIF ( PRESENT( var_int16_1d ) )  THEN
    611601         nc_stat = NF90_PUT_VAR( file_id, var_id, var_int16_1d,            &
    612602                                 start = bounds_start - bounds_origin + 1, &
    613                                  count = value_count )
     603                                 count = value_counts )
    614604      ELSEIF ( PRESENT( var_int16_2d ) )  THEN
    615605         nc_stat = NF90_PUT_VAR( file_id, var_id, var_int16_2d,            &
    616606                                 start = bounds_start - bounds_origin + 1, &
    617                                  count = value_count )
     607                                 count = value_counts )
    618608      ELSEIF ( PRESENT( var_int16_3d ) )  THEN
    619609         nc_stat = NF90_PUT_VAR( file_id, var_id, var_int16_3d,            &
    620610                                 start = bounds_start - bounds_origin + 1, &
    621                                  count = value_count )
     611                                 count = value_counts )
    622612      !-- 32bit integer output
    623613      ELSEIF ( PRESENT( var_int32_0d ) )  THEN
    624614         nc_stat = NF90_PUT_VAR( file_id, var_id, (/ var_int32_0d /),      &
    625615                                 start = bounds_start - bounds_origin + 1, &
    626                                  count = value_count )
     616                                 count = value_counts )
    627617      ELSEIF ( PRESENT( var_int32_1d ) )  THEN
    628618         nc_stat = NF90_PUT_VAR( file_id, var_id, var_int32_1d,            &
    629619                                 start = bounds_start - bounds_origin + 1, &
    630                                  count = value_count )
     620                                 count = value_counts )
    631621      ELSEIF ( PRESENT( var_int32_2d ) )  THEN
    632622         nc_stat = NF90_PUT_VAR( file_id, var_id, var_int32_2d,            &
    633623                                 start = bounds_start - bounds_origin + 1, &
    634                                  count = value_count )
     624                                 count = value_counts )
    635625      ELSEIF ( PRESENT( var_int32_3d ) )  THEN
    636626         nc_stat = NF90_PUT_VAR( file_id, var_id, var_int32_3d,            &
    637627                                 start = bounds_start - bounds_origin + 1, &
    638                                  count = value_count )
     628                                 count = value_counts )
    639629      !-- working-precision integer output
    640630      ELSEIF ( PRESENT( var_intwp_0d ) )  THEN
    641631         nc_stat = NF90_PUT_VAR( file_id, var_id, (/ var_intwp_0d /),      &
    642632                                 start = bounds_start - bounds_origin + 1, &
    643                                  count = value_count )
     633                                 count = value_counts )
    644634      ELSEIF ( PRESENT( var_intwp_1d ) )  THEN
    645635         nc_stat = NF90_PUT_VAR( file_id, var_id, var_intwp_1d,            &
    646636                                 start = bounds_start - bounds_origin + 1, &
    647                                  count = value_count )
     637                                 count = value_counts )
    648638      ELSEIF ( PRESENT( var_intwp_2d ) )  THEN
    649639         nc_stat = NF90_PUT_VAR( file_id, var_id, var_intwp_2d,            &
    650640                                 start = bounds_start - bounds_origin + 1, &
    651                                  count = value_count )
     641                                 count = value_counts )
    652642      ELSEIF ( PRESENT( var_intwp_3d ) )  THEN
    653643         nc_stat = NF90_PUT_VAR( file_id, var_id, var_intwp_3d,            &
    654644                                 start = bounds_start - bounds_origin + 1, &
    655                                  count = value_count )
     645                                 count = value_counts )
    656646      !-- 32bit real output
    657647      ELSEIF ( PRESENT( var_real32_0d ) )  THEN
    658648         nc_stat = NF90_PUT_VAR( file_id, var_id, (/ var_real32_0d /),     &
    659649                                 start = bounds_start - bounds_origin + 1, &
    660                                  count = value_count )
     650                                 count = value_counts )
    661651      ELSEIF ( PRESENT( var_real32_1d ) )  THEN
    662652         nc_stat = NF90_PUT_VAR( file_id, var_id, var_real32_1d,           &
    663653                                 start = bounds_start - bounds_origin + 1, &
    664                                  count = value_count )
     654                                 count = value_counts )
    665655      ELSEIF ( PRESENT( var_real32_2d ) )  THEN
    666656         nc_stat = NF90_PUT_VAR( file_id, var_id, var_real32_2d,           &
    667657                                 start = bounds_start - bounds_origin + 1, &
    668                                  count = value_count )
     658                                 count = value_counts )
    669659      ELSEIF ( PRESENT( var_real32_3d ) )  THEN
    670660         nc_stat = NF90_PUT_VAR( file_id, var_id, var_real32_3d,           &
    671661                                 start = bounds_start - bounds_origin + 1, &
    672                                  count = value_count )
     662                                 count = value_counts )
    673663      !-- 64bit real output
    674664      ELSEIF ( PRESENT( var_real64_0d ) )  THEN
    675665         nc_stat = NF90_PUT_VAR( file_id, var_id, (/ var_real64_0d /),     &
    676666                                 start = bounds_start - bounds_origin + 1, &
    677                                  count = value_count )
     667                                 count = value_counts )
    678668      ELSEIF ( PRESENT( var_real64_1d ) )  THEN
    679669         nc_stat = NF90_PUT_VAR( file_id, var_id, var_real64_1d,           &
    680670                                 start = bounds_start - bounds_origin + 1, &
    681                                  count = value_count )
     671                                 count = value_counts )
    682672      ELSEIF ( PRESENT( var_real64_2d ) )  THEN
    683673         nc_stat = NF90_PUT_VAR( file_id, var_id, var_real64_2d,           &
    684674                                 start = bounds_start - bounds_origin + 1, &
    685                                  count = value_count )
     675                                 count = value_counts )
    686676      ELSEIF ( PRESENT( var_real64_3d ) )  THEN
    687677         nc_stat = NF90_PUT_VAR( file_id, var_id, var_real64_3d,           &
    688678                                 start = bounds_start - bounds_origin + 1, &
    689                                  count = value_count )
     679                                 count = value_counts )
    690680      !-- working-precision real output
    691681      ELSEIF ( PRESENT( var_realwp_0d ) )  THEN
    692682         nc_stat = NF90_PUT_VAR( file_id, var_id, (/ var_realwp_0d /),     &
    693683                                 start = bounds_start - bounds_origin + 1, &
    694                                  count = value_count )
     684                                 count = value_counts )
    695685      ELSEIF ( PRESENT( var_realwp_1d ) )  THEN
    696686         nc_stat = NF90_PUT_VAR( file_id, var_id, var_realwp_1d,           &
    697687                                 start = bounds_start - bounds_origin + 1, &
    698                                  count = value_count )
     688                                 count = value_counts )
    699689      ELSEIF ( PRESENT( var_realwp_2d ) )  THEN
    700690         nc_stat = NF90_PUT_VAR( file_id, var_id, var_realwp_2d,           &
    701691                                 start = bounds_start - bounds_origin + 1, &
    702                                  count = value_count )
     692                                 count = value_counts )
    703693      ELSEIF ( PRESENT( var_realwp_3d ) )  THEN
    704694         nc_stat = NF90_PUT_VAR( file_id, var_id, var_realwp_3d,           &
    705695                                 start = bounds_start - bounds_origin + 1, &
    706                                  count = value_count )
     696                                 count = value_counts )
    707697      ELSE
    708698         return_value = 1
     
    736726            IF ( nc_stat == NF90_NOERR )  THEN
    737727               WRITE( temp_string, * )  TRIM( temp_string ) // '; given variable bounds: ' //  &
    738                   'start=', bounds_start, ', end=', bounds_end, '; file dimension bounds: ' // &
    739                   'start=', bounds_origin, ', end=', bounds_origin + dim_lengths - 1
     728                  'start=', bounds_start, ', count=', value_counts, ', origin=', bounds_origin
    740729               CALL internal_message( 'error', routine_name //     &
    741730                                      ': error while writing: ' // &
  • palm/trunk/UTIL/binary_to_netcdf.f90

    r4107 r4123  
    781781   INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  data_count_per_dimension  !< data count of variable per dimension
    782782   INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  bounds_start              !< lower bounds of variable
    783    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  bounds_end                !< upper bounds of variable
    784783   INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  bounds_origin             !< lower bounds of dimensions in output file
    785784
     
    866865
    867866            ALLOCATE( bounds_start(1:n_dim) )
    868             ALLOCATE( bounds_end(1:n_dim) )
    869867            ALLOCATE( bounds_origin(1:n_dim) )
    870868            ALLOCATE( start_positions(1:n_dim) )
     
    872870
    873871            READ( bin_file_unit ) ( bounds_start(i), i = 1, n_dim )
    874             READ( bin_file_unit ) ( bounds_end(i), i = 1, n_dim )
     872            READ( bin_file_unit ) ( data_count_per_dimension(i), i = 1, n_dim )
    875873            READ( bin_file_unit ) ( bounds_origin(i), i = 1, n_dim )
    876874
     
    878876            CALL internal_message( 'debug', routine_name // &
    879877                                   ': bounds_start = ' // TRIM( temp_string ) )
    880             WRITE( temp_string, * ) bounds_end
     878            WRITE( temp_string, * ) data_count_per_dimension
    881879            CALL internal_message( 'debug', routine_name // &
    882                                    ': bounds_end = ' // TRIM( temp_string ) )
     880                                   ': data_count_per_dimension = ' // TRIM( temp_string ) )
    883881            WRITE( temp_string, * ) bounds_origin
    884882            CALL internal_message( 'debug', routine_name // &
     
    888886
    889887            DO  i = 1, n_dim
    890                data_count = data_count * ( bounds_end(i) - bounds_start(i) + 1 )
     888               data_count = data_count * data_count_per_dimension(i)
    891889               start_positions(i) = bounds_start(i) - bounds_origin(i) + 1
    892                data_count_per_dimension(i) = bounds_end(i) - bounds_start(i) + 1
    893890            ENDDO
    894891
     
    981978            DEALLOCATE( data_count_per_dimension )
    982979            DEALLOCATE( bounds_start )
    983             DEALLOCATE( bounds_end )
    984980            DEALLOCATE( bounds_origin )
    985981
Note: See TracChangeset for help on using the changeset viewer.