Ignore:
Timestamp:
Mar 8, 2016 5:49:27 AM (8 years ago)
Author:
raasch
Message:

pmc-change in server-client get-put, spectra-directives removed, spectra-package modularized

File:
1 edited

Legend:

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

    r1784 r1786  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! cpp-directives for spectra removed, immediate return if no spectra levels are
     22! given
    2223!
    2324! Former revisions:
     
    7374 
    7475#if defined( __netcdf )
    75 #if defined( __spectra )
    76 
    7776    USE control_parameters,                                                    &
    7877        ONLY:  average_count_sp, averaging_interval_sp, dosp_time_count,       &
     
    9392
    9493    USE spectrum,                                                              &
    95         ONLY:  data_output_sp, spectra_direction
     94        ONLY:  comp_spectra_level, data_output_sp, spectra_direction
    9695
    9796    USE statistics,                                                            &
     
    110109
    111110    CALL cpu_log( log_point(31), 'data_output_spectra', 'start' )
     111
     112!
     113!-- Check if user gave any levels for spectra to be calculated
     114    IF ( comp_spectra_level(1) == 999999 )  RETURN
    112115
    113116!
     
    206209
    207210#endif
    208 #endif
    209211 END SUBROUTINE data_output_spectra
    210212
     
    299301
    300302
    301 #if defined( __spectra )
    302303!------------------------------------------------------------------------------!
    303304! Description:
     
    714715
    715716 END SUBROUTINE data_output_spectra_y
    716 #endif
Note: See TracChangeset for help on using the changeset viewer.