Ignore:
Timestamp:
Oct 24, 2017 1:49:46 PM (7 years ago)
Author:
Giersch
Message:

Bugfixes for restart runs

File:
1 edited

Legend:

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

    r2575 r2576  
    2525! -----------------
    2626! $Id$
     27! *** end *** marks the end of the standard parameter list of restart files
     28! like it was before revision 2563. To skip also the variables of the modules 
     29! wind_turbine_model_mod, flight_mod and synthetic_turbulence_generator_mod
     30! three new functions has to be defined which are called in skip_var_list.
     31! Adapted binary version number
     32!
     33! 2575 2017-10-24 09:57:58Z maronga
    2734! Renamed phi -> latitude, added longitude
    2835!
     
    276283!-- Make version number check first
    277284    READ ( 13 )  version_on_file
    278     binary_version = '4.3'
     285    binary_version = '4.4'
    279286    IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
    280287       WRITE( message_string, * ) 'version mismatch concerning control ', &
     
    353360!--          increased. The same changes must also be done in write_var_list.
    354361    READ ( 13 )  variable_chr
    355     DO  WHILE ( TRIM( variable_chr ) /= '*** end default ***' )
     362    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
    356363
    357364       SELECT CASE ( TRIM( variable_chr ) )
     
    987994    READ ( 13 )  variable_chr
    988995
    989     DO  WHILE ( TRIM( variable_chr ) /= '*** end default ***' )
     996    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
    990997
    991998       SELECT CASE ( TRIM( variable_chr ) )
     
    10751082 SUBROUTINE skip_var_list
    10761083
     1084    USE control_parameters,                                                    &
     1085        ONLY: wind_turbine, virtual_flight, synthetic_turbulence_generator
     1086
     1087    USE wind_turbine_model_mod,                                                &
     1088        ONLY: wtm_skip_var_list
     1089
     1090    USE flight_mod,                                                            &
     1091        ONLY: flight_skip_var_list
     1092
     1093    USE synthetic_turbulence_generator_mod,                                    &
     1094        ONLY: stg_skip_var_list
     1095
    10771096
    10781097    IMPLICIT NONE
     
    10951114    ENDDO
    10961115
     1116!
     1117!-- In case of virtual flights, skip also variables related to
     1118!-- this module.
     1119    IF ( wind_turbine )  CALL wtm_skip_var_list
     1120
     1121!
     1122!-- In case of virtual flights, skip also variables related to
     1123!-- this module.
     1124    IF ( virtual_flight )  CALL flight_skip_var_list
     1125
     1126!
     1127!-- In case of virtual flights, skip also variables related to
     1128!-- this module.
     1129    IF ( synthetic_turbulence_generator )  CALL stg_skip_var_list
     1130
    10971131
    10981132 END SUBROUTINE skip_var_list
Note: See TracChangeset for help on using the changeset viewer.