Ignore:
Timestamp:
Mar 26, 2018 9:39:22 AM (6 years ago)
Author:
maronga
Message:

renamed all Fortran NAMELISTS

File:
1 edited

Legend:

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

    r2841 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed spectra_par to spectra_parameters
     28!
     29! 2841 2018-02-27 15:02:57Z knoop
    2730! Bugfix: wrong placement of include 'mpif.h' corrected
    2831!
     
    195198
    196199       USE control_parameters,                                                 &
    197            ONLY:  dt_data_output
     200           ONLY:  dt_data_output, message_string
    198201
    199202       IMPLICIT NONE
     
    206209                               spectra_direction
    207210
    208 
     211       NAMELIST /spectra_parameters/                                           &
     212                               averaging_interval_sp, comp_spectra_level,      &
     213                               data_output_sp, dt_dosp, skip_time_dosp,        &
     214                               spectra_direction
    209215!
    210216!--    Position the namelist-file at the beginning (it was already opened in
     
    217223       REWIND ( 11 )
    218224       line = ' '
    219        DO   WHILE ( INDEX( line, '&spectra_par' ) == 0 )
     225       DO   WHILE ( INDEX( line, '&spectra_parameters' ) == 0 )
    220226          READ ( 11, '(A)', END=10 )  line
    221227       ENDDO
     
    224230!
    225231!--    Read namelist
    226        READ ( 11, spectra_par )
     232       READ ( 11, spectra_parameters )
    227233
    228234!
     
    235241       calculate_spectra = .TRUE.
    236242
    237  10    CONTINUE
     243       GOTO 12
     244!
     245!--    Try to find the old namelist
     246 10    REWIND ( 11 )
     247       line = ' '
     248       DO   WHILE ( INDEX( line, '&spectra_par' ) == 0 )
     249          READ ( 11, '(A)', END=12 )  line
     250       ENDDO
     251       BACKSPACE ( 11 )
     252
     253!
     254!--    Read namelist
     255       READ ( 11, spectra_par )
     256
     257       
     258       message_string = 'namelist spectra_par is deprecated and will be ' // &
     259                     'removed in near future. Please &use namelist ' //      &
     260                     'spectra_parameters instead'
     261       CALL message( 'spectra_parin', 'PA0487', 0, 1, 0, 6, 0 )
     262!
     263!--    Default setting of dt_dosp here (instead of check_parameters), because
     264!--    its current value is needed in init_pegrid
     265       IF ( dt_dosp == 9999999.9_wp )  dt_dosp = dt_data_output
     266
     267!
     268!--    Set general switch that spectra shall be calculated
     269       calculate_spectra = .TRUE.
     270       
     271       
     272 12    CONTINUE
    238273
    239274    END SUBROUTINE spectra_parin
Note: See TracChangeset for help on using the changeset viewer.