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/virtual_flight_mod.f90

    r2894 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed flight_par to virtual_flight_parameters
     28!
     29! 2894 2018-03-15 09:17:58Z Giersch
    2730! variable named found has been introduced for checking if restart data was
    2831! found, reading of restart strings has been moved completely to
     
    218221
    219222       USE control_parameters,                                                 &
    220            ONLY:  initializing_actions 
     223           ONLY:  initializing_actions, message_string 
    221224     
    222225       IMPLICIT NONE
     
    227230                              flight_level, max_elev_change, rate_of_climb,    &
    228231                              speed_agl, x_end, x_start, y_end, y_start
    229                              
     232 
     233
     234       NAMELIST /virtual_flight_parameters/                                    &
     235                              flight_angle, flight_end, flight_begin, leg_mode,&
     236                              flight_level, max_elev_change, rate_of_climb,    &
     237                              speed_agl, x_end, x_start, y_end, y_start
    230238!
    231239!--    Try to find the namelist flight_par
    232240       REWIND ( 11 )
    233241       line = ' '
    234        DO   WHILE ( INDEX( line, '&flight_par' ) == 0 )
     242       DO   WHILE ( INDEX( line, '&virtual_flight_parameters' ) == 0 )
    235243          READ ( 11, '(A)', END=10 )  line
    236244       ENDDO
     
    239247!
    240248!--    Read namelist
    241        READ ( 11, flight_par )
     249       READ ( 11, virtual_flight_parameters )
    242250!
    243251!--    Set switch that virtual flights shall be carried out
    244252       virtual_flight = .TRUE.
    245253
    246 
    247  10    CONTINUE
     254       GOTO 12
     255!
     256!--    Try to find the old namelist
     257 10    REWIND ( 11 )
     258       line = ' '
     259       DO   WHILE ( INDEX( line, '&flight_par' ) == 0 )
     260          READ ( 11, '(A)', END=12 )  line
     261       ENDDO
     262       BACKSPACE ( 11 )
     263
     264!
     265!--    Read namelist
     266       READ ( 11, flight_par )
     267       
     268       message_string = 'namelist flight_par is deprecated and will be ' // &
     269                     'removed in near future. Please &use namelist ' //     &
     270                     'virtual_flight_parameters instead'
     271       CALL message( 'flight_parin', 'PA0487', 0, 1, 0, 6, 0 )     
     272!
     273!--    Set switch that virtual flights shall be carried out
     274       virtual_flight = .TRUE.
     275
     276 12    CONTINUE
    248277
    249278    END SUBROUTINE flight_parin
Note: See TracChangeset for help on using the changeset viewer.