Ignore:
Timestamp:
Mar 6, 2016 6:36:17 PM (8 years ago)
Author:
raasch
Message:

NetCDF routines modularized; new parameter netcdf_deflate; further changes in the pmc

File:
1 edited

Legend:

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

    r1683 r1783  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! name change of netcdf routines and module + related changes
    2222!
    2323! Former revisions:
     
    6969 SUBROUTINE data_output_spectra
    7070 
     71#if defined( __netcdf )
    7172#if defined( __spectra )
    7273
     
    8182    USE kinds
    8283
    83     USE netcdf_control
     84    USE NETCDF
     85
     86    USE netcdf_interface,                                                      &
     87        ONLY:  id_set_sp, id_var_time_sp, nc_stat, netcdf_handle_error
    8488
    8589    USE pegrid
     
    116120       dosp_time_count = dosp_time_count + 1
    117121
    118 #if defined( __netcdf )
    119122!
    120123!--    Update the spectra time axis
     
    122125                               (/ time_since_reference_point /), &
    123126                               start = (/ dosp_time_count /), count = (/ 1 /) )
    124        CALL handle_netcdf_error( 'data_output_spectra', 47 )
    125 #endif
     127       CALL netcdf_handle_error( 'data_output_spectra', 47 )
    126128
    127129!
     
    201203
    202204#endif
     205#endif
    203206 END SUBROUTINE data_output_spectra
    204207
     
    226229    USE kinds
    227230
    228     USE netcdf_control
     231    USE NETCDF
     232
     233    USE netcdf_interface,                                                      &
     234        ONLY:  id_set_sp, id_var_dospx, id_var_dospy, nc_stat,                 &
     235               netcdf_handle_error
    229236
    230237    USE spectrum,                                                              &
     
    261268                                  start = (/ 1, k, dosp_time_count /), &
    262269                                  count = (/ nx/2, 1, 1 /) )
    263           CALL handle_netcdf_error( 'data_output_spectra', 348 )
     270          CALL netcdf_handle_error( 'data_output_spectra', 348 )
    264271
    265272       ENDDO
     
    279286                                  start = (/ 1, k, dosp_time_count /), &
    280287                                  count = (/ ny/2, 1, 1 /) )
    281           CALL handle_netcdf_error( 'data_output_spectra', 349 )
     288          CALL netcdf_handle_error( 'data_output_spectra', 349 )
    282289
    283290       ENDDO
Note: See TracChangeset for help on using the changeset viewer.