Changeset 1745


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

Bugfix:calculation of time levels for parallel NetCDF output

Location:
palm/trunk/SOURCE
Files:
5 edited

Legend:

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

    r1683 r1745  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Bugfix: added MPI barrier after deleting existing non-extendable file by PE0
    2222!
    2323! Former revisions:
     
    647647                CALL handle_netcdf_error( 'check_open', 21 )
    648648                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
    649              ENDIF
    650 
    651           ENDIF         
     649#if defined( __parallel ) && ! defined ( __check )
     650!
     651!--             Set a barrier in order to assure that PE0 deleted the old file
     652!--             before any other processor tries to open a new file
     653                CALL MPI_BARRIER( comm2d, ierr )
     654#endif
     655             ENDIF
     656
     657          ENDIF
    652658
    653659          IF ( .NOT. netcdf_extend )  THEN
     
    703709                CALL handle_netcdf_error( 'check_open', 24 )
    704710                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
    705              ENDIF
    706 
    707           ENDIF         
     711#if defined( __parallel ) && ! defined ( __check )
     712!
     713!--             Set a barrier in order to assure that PE0 deleted the old file
     714!--             before any other processor tries to open a new file
     715                CALL MPI_BARRIER( comm2d, ierr )
     716#endif
     717             ENDIF
     718
     719          ENDIF
    708720
    709721          IF ( .NOT. netcdf_extend )  THEN
     
    759771                CALL handle_netcdf_error( 'check_open', 27 )
    760772                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
    761              ENDIF
    762 
    763           ENDIF         
     773#if defined( __parallel ) && ! defined ( __check )
     774!
     775!--             Set a barrier in order to assure that PE0 deleted the old file
     776!--             before any other processor tries to open a new file
     777                CALL MPI_BARRIER( comm2d, ierr )
     778#endif
     779             ENDIF
     780
     781          ENDIF
    764782
    765783          IF ( .NOT. netcdf_extend )  THEN
     
    895913                nc_stat = NF90_CLOSE( id_set_3d(av) )
    896914                CALL handle_netcdf_error( 'check_open', 36 )
    897                 CALL local_system('rm ' // TRIM( filename ) )
    898              ENDIF
    899 
    900           ENDIF         
     915                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
     916#if defined( __parallel ) && ! defined ( __check )
     917!
     918!--             Set a barrier in order to assure that PE0 deleted the old file
     919!--             before any other processor tries to open a new file
     920                CALL MPI_BARRIER( comm2d, ierr )
     921#endif
     922
     923             ENDIF
     924
     925          ENDIF
    901926
    902927          IF ( .NOT. netcdf_extend )  THEN
     
    9911016                nc_stat = NF90_CLOSE( id_set_prt )
    9921017                CALL handle_netcdf_error( 'check_open', 42 )
    993                 CALL local_system( 'rm ' // filename )
     1018                CALL local_system( 'rm ' // TRIM( filename ) )
    9941019             ENDIF
    9951020
  • 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
  • palm/trunk/SOURCE/data_output_2d.f90

    r1704 r1745  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Bugfix: test if time axis limit exceeds moved to point after call of check_open
    2222!
    2323! Former revisions:
     
    234234    IF ( mode == 'xz'  .AND.  .NOT. data_output_xz(av) )  RETURN
    235235    IF ( mode == 'yz'  .AND.  .NOT. data_output_yz(av) )  RETURN
    236 !
    237 !-- For parallel netcdf output the time axis must be limited. Return, if this
    238 !-- limit is exceeded. This could be the case, if the simulated time exceeds
    239 !-- the given end time by the length of the given output interval.
    240     IF ( netcdf_data_format > 4 )  THEN
    241        IF ( mode == 'xy'  .AND.  do2d_xy_time_count(av) + 1 >                  &
    242             ntdim_2d_xy(av) )  THEN
    243           WRITE ( message_string, * ) 'Output of xy cross-sections is not ',   &
    244                           'given at t=', simulated_time, '&because the',       &
    245                           ' maximum number of output time levels is exceeded.'
    246           CALL message( 'data_output_2d', 'PA0384', 0, 1, 0, 6, 0 )         
    247           RETURN
    248        ENDIF
    249        IF ( mode == 'xz'  .AND.  do2d_xz_time_count(av) + 1 >                  &
    250             ntdim_2d_xz(av) )  THEN
    251           WRITE ( message_string, * ) 'Output of xz cross-sections is not ',   &
    252                           'given at t=', simulated_time, '&because the',       &
    253                           ' maximum number of output time levels is exceeded.'
    254           CALL message( 'data_output_2d', 'PA0385', 0, 1, 0, 6, 0 )         
    255           RETURN
    256        ENDIF
    257        IF ( mode == 'yz'  .AND.  do2d_yz_time_count(av) + 1 >                  &
    258             ntdim_2d_yz(av) )  THEN
    259           WRITE ( message_string, * ) 'Output of yz cross-sections is not ',   &
    260                           'given at t=', simulated_time, '&because the',       &
    261                           ' maximum number of output time levels is exceeded.'
    262           CALL message( 'data_output_2d', 'PA0386', 0, 1, 0, 6, 0 )         
    263           RETURN
    264        ENDIF
    265     ENDIF
    266236
    267237    CALL cpu_log (log_point(3),'data_output_2d','start')
     
    372342
    373343    END SELECT
     344
     345!
     346!-- For parallel netcdf output the time axis must be limited. Return, if this
     347!-- limit is exceeded. This could be the case, if the simulated time exceeds
     348!-- the given end time by the length of the given output interval.
     349    IF ( netcdf_data_format > 4 )  THEN
     350       IF ( mode == 'xy'  .AND.  do2d_xy_time_count(av) + 1 >                  &
     351            ntdim_2d_xy(av) )  THEN
     352          WRITE ( message_string, * ) 'Output of xy cross-sections is not ',   &
     353                          'given at t=', simulated_time, '&because the',       &
     354                          ' maximum number of output time levels is exceeded.'
     355          CALL message( 'data_output_2d', 'PA0384', 0, 1, 0, 6, 0 )
     356          CALL cpu_log( log_point(3), 'data_output_2d', 'stop' )
     357          RETURN
     358       ENDIF
     359       IF ( mode == 'xz'  .AND.  do2d_xz_time_count(av) + 1 >                  &
     360            ntdim_2d_xz(av) )  THEN
     361          WRITE ( message_string, * ) 'Output of xz cross-sections is not ',   &
     362                          'given at t=', simulated_time, '&because the',       &
     363                          ' maximum number of output time levels is exceeded.'
     364          CALL message( 'data_output_2d', 'PA0385', 0, 1, 0, 6, 0 )
     365          CALL cpu_log( log_point(3), 'data_output_2d', 'stop' )
     366          RETURN
     367       ENDIF
     368       IF ( mode == 'yz'  .AND.  do2d_yz_time_count(av) + 1 >                  &
     369            ntdim_2d_yz(av) )  THEN
     370          WRITE ( message_string, * ) 'Output of yz cross-sections is not ',   &
     371                          'given at t=', simulated_time, '&because the',       &
     372                          ' maximum number of output time levels is exceeded.'
     373          CALL message( 'data_output_2d', 'PA0386', 0, 1, 0, 6, 0 )
     374          CALL cpu_log( log_point(3), 'data_output_2d', 'stop' )
     375          RETURN
     376       ENDIF
     377    ENDIF
    374378
    375379!
  • palm/trunk/SOURCE/data_output_3d.f90

    r1692 r1745  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Bugfix: test if time axis limit exceeds moved to point after call of check_open
    2222!
    2323! Former revisions:
     
    176176!-- Return, if nothing to output
    177177    IF ( do3d_no(av) == 0 )  RETURN
    178 !
    179 !-- For parallel netcdf output the time axis must be limited. Return, if this
    180 !-- limit is exceeded. This could be the case, if the simulated time exceeds
    181 !-- the given end time by the length of the given output interval.
    182     IF ( netcdf_data_format > 4 )  THEN
    183        IF ( do3d_time_count(av) + 1 > ntdim_3d(av) )  THEN
    184           WRITE ( message_string, * ) 'Output of 3d data is not given at t=',  &
    185                                       simulated_time, '&because the maximum ', &
    186                                       'number of output time levels is ',      &
    187                                       'exceeded.'
    188           CALL message( 'data_output_3d', 'PA0387', 0, 1, 0, 6, 0 )         
    189           RETURN
    190        ENDIF
    191     ENDIF
    192178
    193179    CALL cpu_log (log_point(14),'data_output_3d','start')
     
    209195       CALL check_open( 106+av*10 )
    210196    ENDIF
     197
     198!
     199!-- For parallel netcdf output the time axis must be limited. Return, if this
     200!-- limit is exceeded. This could be the case, if the simulated time exceeds
     201!-- the given end time by the length of the given output interval.
     202    IF ( netcdf_data_format > 4 )  THEN
     203       IF ( do3d_time_count(av) + 1 > ntdim_3d(av) )  THEN
     204          WRITE ( message_string, * ) 'Output of 3d data is not given at t=',  &
     205                                      simulated_time, '&because the maximum ', &
     206                                      'number of output time levels is ',      &
     207                                      'exceeded.'
     208          CALL message( 'data_output_3d', 'PA0387', 0, 1, 0, 6, 0 )
     209          CALL cpu_log( log_point(14), 'data_output_3d', 'stop' )
     210          RETURN
     211       ENDIF
     212    ENDIF
     213    WRITE(9,*) '___hier4'
     214    CALL local_flush(9)
    211215
    212216!
  • palm/trunk/SOURCE/netcdf.f90

    r1692 r1745  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Bugfix: recalculating ntdim_3d, ntdim_2d_xy/xz/yz when checking the
     22!         extensibility of an existing file (only when using parallel NetCDF).
    2223!
    2324! Former revisions:
     
    112113!> Parameter av can assume values 0 (non-averaged data) and 1 (time averaged
    113114!> data)
     115!>
     116!> @todo calculation of output time levels for parallel NetCDF still does not
     117!>       cover every exception (change of dt_do, end_time in restart)
    114118!------------------------------------------------------------------------------!
    115119#if defined( __ibmy_special )
     
    131135               dopr_time_count, dopts_time_count, dots_time_count,             &
    132136               dosp_time_count, do2d, do2d_xz_time_count, do3d,                &
    133                do2d_yz_time_count, mask_size, do2d_xy_time_count,              &
    134                do3d_time_count, domask_time_count, mask_i_global,              &
     137               do2d_yz_time_count, dt_data_output_av, dt_do2d_xy, dt_do2d_xz,  &
     138               dt_do2d_yz, dt_do3d, mask_size, do2d_xy_time_count,             &
     139               do3d_time_count, domask_time_count, end_time, mask_i_global,    &
    135140               mask_j_global, mask_k_global, message_string, mid,              &
    136141               netcdf_data_format, netcdf_precision, ntdim_2d_xy,              &
    137142               ntdim_2d_xz, ntdim_2d_yz, ntdim_3d, nz_do3d, prt_time_count,    &
    138               run_description_header, section, simulated_time, topography
     143               run_description_header, section, simulated_time,                &
     144               simulated_time_at_begin, skip_time_data_output_av,              &
     145               skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,        &
     146               skip_time_do3d, topography
    139147
    140148    USE grid_variables,                                                        &
     
    211219    INTEGER(iwp) ::  ns_do                                   !< actual value of ns for soil model data
    212220    INTEGER(iwp) ::  ns_old                                  !<
    213     INTEGER(iwp) ::  ntime_count                             !<
     221    INTEGER(iwp) ::  ntime_count                             !< number of time levels found in file
    214222    INTEGER(iwp) ::  nz_old                                  !<
    215223
     
    233241    LOGICAL, SAVE ::  init_netcdf = .FALSE.                  !<
    234242
    235     REAL(wp), DIMENSION(1) ::  last_time_coordinate          !<
     243    REAL(wp), DIMENSION(1) ::  last_time_coordinate          !< last time value in file
    236244
    237245    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  netcdf_data    !<
     
    14601468
    14611469          IF ( netcdf_data_format > 4 )  THEN
     1470!
     1471!--          Set needed time levels (ntdim) to
     1472!--          saved time levels + to be saved time levels.
     1473             IF ( av == 0 )  THEN
     1474                ntdim_3d(0) = do3d_time_count(0) + CEILING(                &
     1475                              ( end_time - MAX( skip_time_do3d,            &
     1476                                                simulated_time_at_begin )  &
     1477                              ) / dt_do3d )
     1478             ELSE
     1479                ntdim_3d(1) = do3d_time_count(1) + CEILING(                &
     1480                              ( end_time - MAX( skip_time_data_output_av,  &
     1481                                                simulated_time_at_begin )  &
     1482                              ) / dt_data_output_av )
     1483             ENDIF
     1484
     1485!
     1486!--          Check if the needed number of output time levels is increased
     1487!--          compared to the number of time levels in the existing file.
    14621488             IF ( ntdim_3d(av) > ntime_count )  THEN
    14631489                message_string = 'netCDF file for volume data ' // &
     
    14661492                                 'e the number of output time levels&has b' // &
    14671493                                 'een increased compared to the previous s' // &
    1468                                  'imulation.' //                                &
     1494                                 'imulation.' //                               &
    14691495                                 '&New file is created instead.'
    14701496                CALL message( 'define_netcdf_header', 'PA0388', 0, 1, 0, 6, 0 )
    14711497                do3d_time_count(av) = 0
    14721498                extend = .FALSE.
     1499!
     1500!--             Recalculate the needed time levels for the new file.
     1501                IF ( av == 0 )  THEN
     1502                   ntdim_3d(0) = CEILING(                               &
     1503                           ( end_time - MAX( skip_time_do3d,            &
     1504                                             simulated_time_at_begin )  &
     1505                           ) / dt_do3d )
     1506                ELSE
     1507                   ntdim_3d(1) = CEILING(                               &
     1508                           ( end_time - MAX( skip_time_data_output_av,  &
     1509                                             simulated_time_at_begin )  &
     1510                           ) / dt_data_output_av )
     1511                ENDIF
    14731512                RETURN
    14741513             ENDIF
     
    22192258
    22202259          IF ( netcdf_data_format > 4 )  THEN
     2260!
     2261!--          Set needed time levels (ntdim) to
     2262!--          saved time levels + to be saved time levels.
     2263             IF ( av == 0 )  THEN
     2264                ntdim_2d_xy(0) = do2d_xy_time_count(0) + CEILING(             &
     2265                                 ( end_time - MAX( skip_time_do2d_xy,         &
     2266                                                   simulated_time_at_begin )  &
     2267                                 ) / dt_do2d_xy )
     2268             ELSE
     2269                ntdim_2d_xy(1) = do2d_xy_time_count(1) + CEILING(             &
     2270                                 ( end_time - MAX( skip_time_data_output_av,  &
     2271                                                   simulated_time_at_begin )  &
     2272                                 ) / dt_data_output_av )
     2273             ENDIF
     2274
     2275!
     2276!--          Check if the needed number of output time levels is increased
     2277!--          compared to the number of time levels in the existing file.
    22212278             IF ( ntdim_2d_xy(av) > ntime_count )  THEN
    22222279                message_string = 'netCDF file for cross sections ' //          &
     
    22252282                                 'e the number of output time levels&has b' // &
    22262283                                 'een increased compared to the previous s' // &
    2227                                  'imulation.' //                                &
     2284                                 'imulation.' //                               &
    22282285                                 '&New file is created instead.'
    22292286                CALL message( 'define_netcdf_header', 'PA0389', 0, 1, 0, 6, 0 )
    22302287                do2d_xy_time_count(av) = 0
    22312288                extend = .FALSE.
     2289!
     2290!--             Recalculate the needed time levels for the new file.
     2291                IF ( av == 0 )  THEN
     2292                   ntdim_2d_xy(0) = CEILING(                            &
     2293                           ( end_time - MAX( skip_time_do2d_xy,         &
     2294                                             simulated_time_at_begin )  &
     2295                           ) / dt_do2d_xy )
     2296                ELSE
     2297                   ntdim_2d_xy(1) = CEILING(                            &
     2298                           ( end_time - MAX( skip_time_data_output_av,  &
     2299                                             simulated_time_at_begin )  &
     2300                           ) / dt_data_output_av )
     2301                ENDIF
    22322302                RETURN
    22332303             ENDIF
     
    28792949             RETURN
    28802950          ENDIF
    2881          
     2951
    28822952          IF ( netcdf_data_format > 4 )  THEN
     2953!
     2954!--          Set needed time levels (ntdim) to
     2955!--          saved time levels + to be saved time levels.
     2956             IF ( av == 0 )  THEN
     2957                ntdim_2d_xz(0) = do2d_xz_time_count(0) + CEILING(             &
     2958                                 ( end_time - MAX( skip_time_do2d_xz,         &
     2959                                                   simulated_time_at_begin )  &
     2960                                 ) / dt_do2d_xz )
     2961             ELSE
     2962                ntdim_2d_xz(1) = do2d_xz_time_count(1) + CEILING(             &
     2963                                 ( end_time - MAX( skip_time_data_output_av,  &
     2964                                                   simulated_time_at_begin )  &
     2965                                 ) / dt_data_output_av )
     2966             ENDIF
     2967
     2968!
     2969!--          Check if the needed number of output time levels is increased
     2970!--          compared to the number of time levels in the existing file.
    28832971             IF ( ntdim_2d_xz(av) > ntime_count )  THEN
    28842972                message_string = 'netCDF file for cross sections ' // &
     
    28872975                                 'e the number of output time levels&has b' // &
    28882976                                 'een increased compared to the previous s' // &
    2889                                  'imulation.' //                                &
     2977                                 'imulation.' //                               &
    28902978                                 '&New file is created instead.'
    28912979                CALL message( 'define_netcdf_header', 'PA0390', 0, 1, 0, 6, 0 )
    28922980                do2d_xz_time_count(av) = 0
    28932981                extend = .FALSE.
     2982!
     2983!--             Recalculate the needed time levels for the new file.
     2984                IF ( av == 0 )  THEN
     2985                   ntdim_2d_xz(0) = CEILING(                            &
     2986                           ( end_time - MAX( skip_time_do2d_xz,         &
     2987                                             simulated_time_at_begin )  &
     2988                           ) / dt_do2d_xz )
     2989                ELSE
     2990                   ntdim_2d_xz(1) = CEILING(                            &
     2991                           ( end_time - MAX( skip_time_data_output_av,  &
     2992                                             simulated_time_at_begin )  &
     2993                           ) / dt_data_output_av )
     2994                ENDIF
    28942995                RETURN
    28952996             ENDIF
     
    35463647
    35473648          IF ( netcdf_data_format > 4 )  THEN
     3649!
     3650!--          Set needed time levels (ntdim) to
     3651!--          saved time levels + to be saved time levels.
     3652             IF ( av == 0 )  THEN
     3653                ntdim_2d_yz(0) = do2d_yz_time_count(0) + CEILING(             &
     3654                                 ( end_time - MAX( skip_time_do2d_yz,         &
     3655                                                   simulated_time_at_begin )  &
     3656                                 ) / dt_do2d_yz )
     3657             ELSE
     3658                ntdim_2d_yz(1) = do2d_yz_time_count(1) + CEILING(             &
     3659                                 ( end_time - MAX( skip_time_data_output_av,  &
     3660                                                   simulated_time_at_begin )  &
     3661                                 ) / dt_data_output_av )
     3662             ENDIF
     3663
     3664!
     3665!--          Check if the needed number of output time levels is increased
     3666!--          compared to the number of time levels in the existing file.
    35483667             IF ( ntdim_2d_yz(av) > ntime_count )  THEN
    35493668                message_string = 'netCDF file for cross sections ' //          &
     
    35573676                do2d_yz_time_count(av) = 0
    35583677                extend = .FALSE.
     3678!
     3679!--             Recalculate the needed time levels for the new file.
     3680                IF ( av == 0 )  THEN
     3681                   ntdim_2d_yz(0) = CEILING(                            &
     3682                           ( end_time - MAX( skip_time_do2d_yz,         &
     3683                                             simulated_time_at_begin )  &
     3684                           ) / dt_do2d_yz )
     3685                ELSE
     3686                   ntdim_2d_yz(1) = CEILING(                            &
     3687                           ( end_time - MAX( skip_time_data_output_av,  &
     3688                                             simulated_time_at_begin )  &
     3689                           ) / dt_data_output_av )
     3690                ENDIF
    35593691                RETURN
    35603692             ENDIF
     
    51035235    IF ( netcdf_data_format == 1 )  THEN
    51045236!
    5105 !-- Classic netCDF format
    5106     nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id )
     5237!--    Classic netCDF format
     5238       nc_stat = NF90_CREATE( filename, NF90_NOCLOBBER, id )
    51075239
    51085240    ELSEIF ( netcdf_data_format == 2 )  THEN
     
    51245256!--    netCDF4/HDF5 format with classic model flag
    51255257       nc_stat = NF90_CREATE( filename,                                        &
    5126                               IOR( NF90_NOCLOBBER,                              &
     5258                              IOR( NF90_NOCLOBBER,                             &
    51275259                              IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ), id )
    51285260
     
    51325264!--    netCDF4/HDF5 format, parallel
    51335265       nc_stat = NF90_CREATE( filename,                                        &
    5134                               IOR( NF90_NOCLOBBER,                              &
    5135                               IOR( NF90_NETCDF4, NF90_MPIIO ) ),                &
     5266                              IOR( NF90_NOCLOBBER,                             &
     5267                              IOR( NF90_NETCDF4, NF90_MPIIO ) ),               &
    51365268                              id, COMM = comm2d, INFO = MPI_INFO_NULL )
    51375269
     
    51405272!--    netCDF4/HDF5 format with classic model flag, parallel
    51415273       nc_stat = NF90_CREATE( filename,                                        &
    5142                               IOR( NF90_NOCLOBBER,                              &
    5143                               IOR( NF90_MPIIO,                                  &
    5144                               IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ) ),         &
     5274                              IOR( NF90_NOCLOBBER,                             &
     5275                              IOR( NF90_MPIIO,                                 &
     5276                              IOR( NF90_CLASSIC_MODEL, NF90_HDF5 ) ) ),        &
    51455277                              id, COMM = comm2d, INFO = MPI_INFO_NULL )
    51465278
Note: See TracChangeset for help on using the changeset viewer.