Changeset 2563 for palm/trunk


Ignore:
Timestamp:
Oct 19, 2017 3:36:10 PM (7 years ago)
Author:
Giersch
Message:

Restart runs with the usage of the wind turbine model are possible now. Further small at reading/writing restart data

Location:
palm/trunk
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SCRIPTS/NCL/spectra.ncl

    r2030 r2563  
    685685                        res@trXMaxF = max(max_x)
    686686                        res@trYMinF = min(min_y)
    687                         res@trYMaxF = max(max_y)
     687                        res@trYMaxF = max(max_y*10)
    688688                       
    689689                        plot_h(q)  = gsn_csm_xy(wks,x_axis(q,:),\
  • palm/trunk/SOURCE/Makefile

    r2544 r2563  
    2525# -----------------
    2626# $Id$
     27# wind_turbine_model_mod.o and synthetic_turbulence_generator_mod.o were added to
     28# write_var_list.o and virtual_flight_mod.o was deleted from read_var_list.o 
     29#
     30# 2544 2017-10-13 18:09:32Z maronga
    2731# Added date_and_time_mod
    2832#
     
    626630   spectra_mod.o surface_mod.o urban_surface_mod.o
    627631read_var_list.o: modules.o mod_kinds.o model_1d_mod.o netcdf_interface_mod.o plant_canopy_model_mod.o \
    628    spectra_mod.o microphysics_mod.o urban_surface_mod.o vertical_nesting_mod.o virtual_flight_mod.o
     632   spectra_mod.o microphysics_mod.o urban_surface_mod.o vertical_nesting_mod.o
    629633run_control.o: modules.o cpulog_mod.o mod_kinds.o
    630634set_slicer_attributes_dvrp.o: modules.o mod_kinds.o
     
    697701        spectra_mod.o surface_mod.o
    698702write_var_list.o: modules.o mod_kinds.o model_1d_mod.o netcdf_interface_mod.o plant_canopy_model_mod.o\
    699    spectra_mod.o microphysics_mod.o urban_surface_mod.o vertical_nesting_mod.o virtual_flight_mod.o
     703   spectra_mod.o microphysics_mod.o urban_surface_mod.o vertical_nesting_mod.o virtual_flight_mod.o\
     704   wind_turbine_model_mod.o synthetic_turbulence_generator_mod.o
  • palm/trunk/SOURCE/modules.f90

    r2550 r2563  
    2525! -----------------
    2626! $Id$
     27! Variable wind_turbine was added to control_parameters
     28!
     29! 2550 2017-10-16 17:12:01Z boeske
    2730! complex_terrain namelist parameter added
    2831!
     
    12421245    LOGICAL ::  virtual_flight = .FALSE.                     !< use virtual flight model?
    12431246    LOGICAL ::  wall_adjustment = .TRUE.                     !< namelist parameter
     1247    LOGICAL ::  wind_turbine = .FALSE.                       !< flag for use of wind turbine model
    12441248    LOGICAL ::  write_binary = .FALSE.                       !< ENVPAR namelist parameter to steer restart I/O (ENVPAR is created by mrun)
    12451249    LOGICAL ::  ws_scheme_sca = .FALSE.                      !< use Wicker-Skamarock scheme (scalar advection)?
  • palm/trunk/SOURCE/parin.f90

    r2550 r2563  
    2525! -----------------
    2626! $Id$
     27! Changed position where restart files are closed.
     28!
     29! 2550 2017-10-16 17:12:01Z boeske
    2730! Added complex_terrain
    2831!
     
    559562 12       IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
    560563             CALL read_var_list
    561 !
    562 !--          The restart file will be reopened when reading the subdomain data
    563              CALL close_file( 13 )
    564564
    565565!
     
    698698
    699699!
     700!--       The restart file will be reopened when reading the subdomain data
     701          IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
     702             CALL close_file( 13 )
     703          ENDIF
     704
     705!
    700706!--       Check in case of initial run, if the grid point numbers are well
    701707!--       defined and allocate some arrays which are already needed in
  • palm/trunk/SOURCE/prognostic_equations.f90

    r2320 r2563  
    2525! -----------------
    2626! $Id$
     27! Variable wind_turbine moved to module control_parameters
     28!
     29! 2320 2017-07-21 12:47:43Z suehring
    2730! Modularize large-scale forcing and nudging
    2831!
     
    260263               scalar_advec, scalar_advec, simulated_time, sloping_surface,    &
    261264               timestep_scheme, tsc, use_subsidence_tendencies,                &
    262                use_upstream_for_tke, ws_scheme_mom, ws_scheme_sca
     265               use_upstream_for_tke, wind_turbine, ws_scheme_mom,              &
     266               ws_scheme_sca
    263267
    264268    USE cpulog,                                                                &
     
    358362
    359363    USE wind_turbine_model_mod,                                                &
    360         ONLY:  wind_turbine, wtm_tendencies
     364        ONLY:  wtm_tendencies
    361365
    362366
  • palm/trunk/SOURCE/read_var_list.f90

    r2372 r2563  
    2525! -----------------
    2626! $Id$
     27! CALL stg_read_restart_data moved to synthetic_turbulence_generator_mod and
     28! CALL flight_read_restart_data moved to virtual_flights_mod. Furthermore
     29! *** end default *** marks the end of the standard parameter list of restart
     30! files and *** end *** marks the end of all parameter including module
     31! parameter. Therefore the call of flight_skip_var_list becomes unnecessary.
     32!
     33! 2372 2017-08-25 12:37:32Z sward
    2734! y_shift added to vars, version no. increased
    2835!
     
    220227    USE control_parameters
    221228
    222     USE flight_mod,                                                            &
    223         ONLY:  flight_read_restart_data
    224 
    225229    USE grid_variables,                                                        &
    226230        ONLY:  dx, dy
     
    255259               v_max, v_max_ijk, w_max, w_max_ijk
    256260
    257     USE synthetic_turbulence_generator_mod,                                    &
    258         ONLY:  stg_read_restart_data
    259 
    260261    USE vertical_nesting_mod,                                                  &
    261262        ONLY:  vnest_init
     
    272273!-- Make version number check first
    273274    READ ( 13 )  version_on_file
    274     binary_version = '4.2'
     275    binary_version = '4.3'
    275276    IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
    276277       WRITE( message_string, * ) 'version mismatch concerning control ', &
     
    349350!--          increased. The same changes must also be done in write_var_list.
    350351    READ ( 13 )  variable_chr
    351     DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
     352    DO  WHILE ( TRIM( variable_chr ) /= '*** end default ***' )
    352353
    353354       SELECT CASE ( TRIM( variable_chr ) )
     
    842843    ENDDO
    843844
    844     IF ( virtual_flight )  CALL flight_read_restart_data
    845 
    846     IF ( synthetic_turbulence_generator )  CALL stg_read_restart_data
    847845
    848846 END SUBROUTINE read_var_list
     
    984982    READ ( 13 )  variable_chr
    985983
    986     DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
     984    DO  WHILE ( TRIM( variable_chr ) /= '*** end default ***' )
    987985
    988986       SELECT CASE ( TRIM( variable_chr ) )
     
    10721070 SUBROUTINE skip_var_list
    10731071
    1074     USE control_parameters,                                                    &
    1075         ONLY:  virtual_flight
    1076 
    1077     USE flight_mod,                                                            &
    1078         ONLY:  flight_skip_var_list
    10791072
    10801073    IMPLICIT NONE
     
    10961089
    10971090    ENDDO
    1098 !
    1099 !-- In case of virtual flights, skip also variables related to
    1100 !-- this module.
    1101     IF ( virtual_flight )  CALL flight_skip_var_list
    11021091
    11031092
  • palm/trunk/SOURCE/synthetic_turbulence_generator_mod.f90

    r2259 r2563  
    2525! -----------------
    2626! $Id$
     27! stg_read_restart_data is called in stg_parin in the case of a restart run
     28!
     29! 2259 2017-06-08 09:09:11Z gronemeier
    2730! Initial revision
    2831!
     
    194197!-- Public interfaces
    195198    PUBLIC  stg_check_parameters, stg_header, stg_init, stg_main, stg_parin,   &
    196             stg_read_restart_data, stg_write_restart_data
     199            stg_write_restart_data
    197200
    198201!
     
    659662!-- on
    660663    synthetic_turbulence_generator = .TRUE.
     664
     665    IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN
     666       CALL stg_read_restart_data
     667    ENDIF
    661668
    662669 10 CONTINUE
  • palm/trunk/SOURCE/time_integration.f90

    r2365 r2563  
    2525! -----------------
    2626! $Id$
     27! Variable wind_turbine moved to module control_parameters
     28!
     29! 2365 2017-08-21 14:59:59Z kanani
    2730! Vertical grid nesting implemented (SadiqHuq)
    2831!
     
    323326               use_initial_profile_as_reference,                               &
    324327               use_single_reference_value, u_gtrans, v_gtrans, virtual_flight, &
    325                ws_scheme_mom, ws_scheme_sca
     328               wind_turbine, ws_scheme_mom, ws_scheme_sca
    326329
    327330    USE cpulog,                                                                &
     
    400403
    401404    USE wind_turbine_model_mod,                                                &
    402         ONLY:  wind_turbine, wtm_forces
     405        ONLY:  wtm_forces
    403406
    404407    USE vertical_nesting_mod,                                                  &
  • palm/trunk/SOURCE/virtual_flight_mod.f90

    r2271 r2563  
    2525! -----------------
    2626! $Id$
     27! flight_read_restart_data is called in flight_parin in the case of a restart
     28! run. flight_skip_var_list is not necessary anymore due to marker changes in
     29! restart files.
     30!
     31! 2271 2017-06-09 12:34:55Z sward
    2732! Todo added
    2833!
     
    115120    END INTERFACE flight_measurement
    116121   
    117     INTERFACE flight_skip_var_list
    118        MODULE PROCEDURE flight_skip_var_list
    119     END INTERFACE flight_skip_var_list
    120    
    121122    INTERFACE flight_read_restart_data
    122123       MODULE PROCEDURE flight_read_restart_data
     
    133134!-- Public interfaces
    134135    PUBLIC flight_init, flight_header, flight_parin, flight_measurement,       &
    135            flight_skip_var_list, flight_read_restart_data,                     &
    136            flight_write_restart_data
     136           flight_write_restart_data                   
    137137!
    138138!-- Public variables
     
    192192    SUBROUTINE flight_parin
    193193
    194    
     194       USE control_parameters,                                                 &
     195           ONLY:  initializing_actions 
     196     
    195197       IMPLICIT NONE
    196198
     
    216218!--    Set switch that virtual flights shall be carried out
    217219       virtual_flight = .TRUE.
     220
     221       IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN
     222          CALL flight_read_restart_data
     223       ENDIF
    218224
    219225 10    CONTINUE
     
    854860
    855861    END SUBROUTINE flight_check_parameters
    856    
    857 !------------------------------------------------------------------------------!
    858 ! Description:
    859 ! ------------
    860 !> Skipping the flight-module variables from restart-file (binary format).
    861 !------------------------------------------------------------------------------!
    862     SUBROUTINE flight_skip_var_list 
    863            
    864        IMPLICIT NONE
    865        
    866        CHARACTER (LEN=1)  ::  cdum
    867        CHARACTER (LEN=30) ::  variable_chr
    868        
    869        READ ( 13 )  variable_chr
    870        DO  WHILE ( TRIM( variable_chr ) /= '*** end flight ***' )
    871           READ ( 13 )  cdum
    872           READ ( 13 )  variable_chr
    873        ENDDO   
    874        
    875     END SUBROUTINE flight_skip_var_list 
    876862   
    877863!------------------------------------------------------------------------------!
  • palm/trunk/SOURCE/wind_turbine_model_mod.f90

    r2553 r2563  
    2626! -----------------
    2727! $Id$
     28! Restart runs with wind turbine model are possible now. For this purpose, two
     29! new subroutines wtm_write_restart_data and wtm_read_restart_data had to be
     30! defined
     31!
     32! 2553 2017-10-18 08:03:45Z Giersch
    2833! Bugfix of vertical loop in wtm_tendencies to account for different turbine
    2934! heights, bugfix of the interpolation of the u-component concerning the
     
    104109
    105110    USE control_parameters,                                                    &
    106         ONLY:  dt_3d, dz, message_string, simulated_time
     111        ONLY:  dt_3d, dz, message_string, simulated_time, wind_turbine,        &
     112               initializing_actions
    107113
    108114    USE cpulog,                                                                &
     
    124130
    125131    PRIVATE
    126 
    127     LOGICAL ::  wind_turbine=.FALSE.   !< switch for use of wind turbine model
    128132
    129133!
     
    265269    REAL(wp), DIMENSION(:), ALLOCATABLE ::  alpha_attack !<
    266270    REAL(wp), DIMENSION(:), ALLOCATABLE ::  chord        !<
    267     REAL(wp), DIMENSION(:), ALLOCATABLE ::  omega_gen    !< curr. generator speed
    268271    REAL(wp), DIMENSION(:), ALLOCATABLE ::  phi_rel      !<
    269     REAL(wp), DIMENSION(:), ALLOCATABLE ::  pitch_add_old!<
    270272    REAL(wp), DIMENSION(:), ALLOCATABLE ::  torque_total !<
    271273    REAL(wp), DIMENSION(:), ALLOCATABLE ::  thrust_rotor !<
     
    337339    REAL(wp) ::  vs_sysp             !<
    338340    REAL(wp) ::  lp_coeff            !< coeff for the controller low pass filter
    339    
    340     REAL(wp), DIMENSION(:), ALLOCATABLE :: omega_gen_old   !< last gen. speed
    341     REAL(wp), DIMENSION(:), ALLOCATABLE :: omega_gen_f     !< filtered gen. sp
    342     REAL(wp), DIMENSION(:), ALLOCATABLE :: omega_gen_f_old !< last filt. gen. sp
    343     REAL(wp), DIMENSION(:), ALLOCATABLE :: torque_gen      !< generator torque
    344     REAL(wp), DIMENSION(:), ALLOCATABLE :: torque_gen_old  !< last gen. torque
    345341
    346342    REAL(wp), DIMENSION(100) :: omega_rot_l = 0.0_wp !< local rot speed [rad/s]
     343
    347344!
    348345!-- Fixed variables for the yaw controller
     
    362359    INTEGER(iwp)                          ::  WDSHO            !<
    363360
     361!
     362!-- Variables that have to be saved in the binary file for restarts
     363    REAL(wp), DIMENSION(1:100) ::  pitch_add_old           = 0.0_wp  !< old constant pitch angle
     364    REAL(wp), DIMENSION(1:100) ::  omega_gen               = 0.0_wp  !< curr. generator speed
     365    REAL(wp), DIMENSION(1:100) ::  omega_gen_f             = 0.0_wp  !< filtered generator speed
     366    REAL(wp), DIMENSION(1:100) ::  omega_gen_old           = 0.0_wp  !< last generator speed
     367    REAL(wp), DIMENSION(1:100) ::  omega_gen_f_old         = 0.0_wp  !< last filtered generator speed
     368    REAL(wp), DIMENSION(1:100) ::  torque_gen              = 0.0_wp  !< generator torque
     369    REAL(wp), DIMENSION(1:100) ::  torque_gen_old          = 0.0_wp  !< last generator torque
     370
    364371
    365372    SAVE
     
    369376       MODULE PROCEDURE wtm_parin
    370377    END INTERFACE wtm_parin
     378
     379    INTERFACE wtm_write_restart_data
     380       MODULE PROCEDURE wtm_write_restart_data
     381    END INTERFACE wtm_write_restart_data
     382
     383    INTERFACE wtm_read_restart_data
     384       MODULE PROCEDURE wtm_read_restart_data
     385    END INTERFACE wtm_read_restart_data
    371386   
    372387    INTERFACE wtm_check_parameters
     
    410425   
    411426    PUBLIC wtm_check_parameters, wtm_forces, wtm_init, wtm_init_arrays,        &
    412            wtm_parin, wtm_tendencies, wind_turbine
     427           wtm_parin, wtm_write_restart_data, wtm_tendencies
     428
    413429
    414430 CONTAINS
     
    467483       wind_turbine = .TRUE.
    468484
     485       IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN
     486          CALL wtm_read_restart_data
     487       ENDIF
     488
    469489 10    CONTINUE   ! TBD Change from continue, mit ierrn machen
    470490
     
    472492    END SUBROUTINE wtm_parin
    473493
     494
     495!------------------------------------------------------------------------------!
     496! Description:
     497! ------------
     498!> This routine writes the respective restart data.
     499!------------------------------------------------------------------------------!
     500    SUBROUTINE wtm_write_restart_data 
     501
     502       IMPLICIT NONE
     503       
     504       WRITE ( 14 )  'omega_gen                     '
     505       WRITE ( 14 )  omega_gen
     506       WRITE ( 14 )  'omega_gen_f                   '
     507       WRITE ( 14 )  omega_gen_f
     508       WRITE ( 14 )  'omega_gen_f_old               '
     509       WRITE ( 14 )  omega_gen_f_old
     510       WRITE ( 14 )  'omega_gen_old                 '
     511       WRITE ( 14 )  omega_gen_old
     512       WRITE ( 14 )  'omega_rot                     '
     513       WRITE ( 14 )  omega_rot
     514       WRITE ( 14 )  'phi_yaw                       '
     515       WRITE ( 14 )  phi_yaw(:)
     516       WRITE ( 14 )  'pitch_add                     '
     517       WRITE ( 14 )  pitch_add
     518       WRITE ( 14 )  'pitch_add_old                 '
     519       WRITE ( 14 )  pitch_add_old
     520       WRITE ( 14 )  'torque_gen                    '
     521       WRITE ( 14 )  torque_gen
     522       WRITE ( 14 )  'torque_gen_old                '
     523       WRITE ( 14 )  torque_gen_old
     524     
     525       WRITE ( 14 )  '*** end wtm ***               '
     526       
     527    END SUBROUTINE wtm_write_restart_data   
     528
     529
     530!------------------------------------------------------------------------------!
     531! Description:
     532! ------------
     533!> This routine reads the respective restart data.
     534!------------------------------------------------------------------------------!
     535 SUBROUTINE wtm_read_restart_data
     536
     537
     538    IMPLICIT NONE
     539
     540    CHARACTER (LEN=30) ::  variable_chr  !< dummy variable to read string
     541
     542
     543    READ ( 13 )  variable_chr
     544    DO  WHILE ( TRIM( variable_chr ) /= '*** end wtm ***' )
     545
     546       SELECT CASE ( TRIM( variable_chr ) )
     547
     548          CASE ( 'omega_gen' )
     549             READ ( 13 )  omega_gen
     550          CASE ( 'omega_gen_f' )
     551             READ ( 13 )  omega_gen_f
     552          CASE ( 'omega_gen_old' )
     553             READ ( 13 )  omega_gen_old
     554          CASE ( 'omega_gen_f_old' )
     555             READ ( 13 )  omega_gen_f_old
     556          CASE ( 'omega_rot' )
     557             READ ( 13 )  omega_rot
     558          CASE ( 'phi_yaw' )
     559             READ ( 13 )  phi_yaw
     560          CASE ( 'pitch_add' )
     561             READ ( 13 )  pitch_add
     562          CASE ( 'pitch_add_old' )
     563             READ ( 13 )  pitch_add_old
     564          CASE ( 'torque_gen' )
     565             READ ( 13 )  torque_gen
     566          CASE ( 'torque_gen_old' )
     567             READ ( 13 )  torque_gen_old
     568
     569       END SELECT
     570
     571       READ ( 13 )  variable_chr
     572
     573    ENDDO
     574
     575 END SUBROUTINE wtm_read_restart_data
     576
     577
     578!------------------------------------------------------------------------------!
     579! Description:
     580! ------------
     581!> Check namelist parameter
     582!------------------------------------------------------------------------------!
    474583    SUBROUTINE wtm_check_parameters
    475584
     
    594703
    595704!
    596 !--    Allocation of the 1D arrays for speed pitch_control
    597        ALLOCATE( omega_gen(1:nturbines) )
    598        ALLOCATE( omega_gen_old(1:nturbines) )
    599        ALLOCATE( omega_gen_f(1:nturbines) )
    600        ALLOCATE( omega_gen_f_old(1:nturbines) )
    601        ALLOCATE( pitch_add_old(1:nturbines) )
    602        ALLOCATE( torque_gen(1:nturbines) )
    603        ALLOCATE( torque_gen_old(1:nturbines) )
    604 
    605 !
    606705!--    Allocation of the 1D arrays for yaw control
    607706       ALLOCATE( yawdir(1:nturbines) )
     
    672771       thrust_rotor(:)          = 0.0_wp
    673772
    674        omega_gen(:)             = 0.0_wp
    675        omega_gen_old(:)         = 0.0_wp
    676        omega_gen_f(:)           = 0.0_wp
    677        omega_gen_f_old(:)       = 0.0_wp
    678        pitch_add_old(:)         = 0.0_wp
    679        torque_gen(:)            = 0.0_wp
    680        torque_gen_old(:)        = 0.0_wp
    681        
     773       IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
     774          omega_gen(:)             = 0.0_wp
     775          omega_gen_old(:)         = 0.0_wp
     776          omega_gen_f(:)           = 0.0_wp
     777          omega_gen_f_old(:)       = 0.0_wp
     778          pitch_add_old(:)         = 0.0_wp
     779          torque_gen(:)            = 0.0_wp
     780          torque_gen_old(:)        = 0.0_wp
     781       ENDIF
     782
    682783       yawdir(:)                = 0.0_wp
    683784       wdir(:)                  = 0.0_wp
     
    776877          CALL wtm_speed_control
    777878
     879          IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN
     880
     881             DO inot = 1, nturbines
     882
     883                IF ( nxl > i_hub(inot) ) THEN
     884                   torque_gen(inot) = 0.0_wp
     885                   omega_gen_f(inot) = 0.0_wp
     886                   omega_rot_l(inot) = 0.0_wp
     887                ENDIF
     888
     889                IF ( nxr < i_hub(inot) ) THEN
     890                   torque_gen(inot) = 0.0_wp
     891                   omega_gen_f(inot) = 0.0_wp
     892                   omega_rot_l(inot) = 0.0_wp
     893                ENDIF
     894
     895                IF ( nys > j_hub(inot) ) THEN
     896                   torque_gen(inot) = 0.0_wp
     897                   omega_gen_f(inot) = 0.0_wp
     898                   omega_rot_l(inot) = 0.0_wp
     899                ENDIF
     900
     901                IF ( nyn < j_hub(inot) ) THEN
     902                   torque_gen(inot) = 0.0_wp
     903                   omega_gen_f(inot) = 0.0_wp
     904                   omega_rot_l(inot) = 0.0_wp
     905                ENDIF
     906
     907                IF ( ( nxl <= i_hub(inot) ) .AND. ( nxr >= i_hub(inot) ) ) THEN
     908                   IF ( ( nys <= j_hub(inot) ) .AND. ( nyn >= j_hub(inot) ) ) THEN
     909
     910                      omega_rot_l(inot) = omega_gen(inot) / gear_ratio
     911
     912                   ENDIF
     913                ENDIF
     914
     915             END DO
     916
     917          ENDIF
     918
    778919       ENDIF
    779920
     
    814955!
    815956!--    Change yaw angle to rad:
    816        phi_yaw(:) = phi_yaw(:) * pi / 180.0_wp
     957       IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
     958          phi_yaw(:) = phi_yaw(:) * pi / 180.0_wp
     959       ENDIF
    817960
    818961
     
    23662509!--    At the first timestep the torque is set to its maximum to prevent
    23672510!--    an overspeeding of the rotor
    2368        torque_gen_old(:) = max_torque_gen 
     2511       IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
     2512          torque_gen_old(:) = max_torque_gen
     2513       ENDIF 
    23692514     
    23702515    END SUBROUTINE wtm_init_speed_control
  • palm/trunk/SOURCE/write_var_list.f90

    r2372 r2563  
    2525! -----------------
    2626! $Id$
     27! Function call wtm_write_restart_data was added and the end of the standard
     28! parameter list is now marked with *** end default ***. The end of the whole
     29! parameter list including module parameter is marked with *** end ***
     30!
     31! 2372 2017-08-25 12:37:32Z sward
    2732! y_shift added to vars, version no. increased
    2833!
     
    233238        ONLY:  vnest_init
    234239
     240    USE wind_turbine_model_mod,                                                &
     241        ONLY:  wtm_write_restart_data 
     242
    235243    IMPLICIT NONE
    236244
     
    238246
    239247
    240     binary_version = '4.2'
     248    binary_version = '4.3'
    241249
    242250    WRITE ( 14 )  binary_version
     
    739747
    740748!
    741 !-- Set the end-of-file mark
    742     WRITE ( 14 )  '*** end ***                   '
     749!-- Set the end-of-file mark for default parameter
     750    WRITE ( 14 )  '*** end default ***           '
     751
     752!
     753!-- If required, write restart data for wind turbine model.
     754    IF ( wind_turbine )  CALL wtm_write_restart_data
     755
    743756!
    744757!-- If required, write restart data for virtual measurements.
     
    749762    IF ( synthetic_turbulence_generator )  CALL stg_write_restart_data
    750763
     764!
     765!-- Set the end-of-file mark for default parameter
     766    WRITE ( 14 )  '*** end ***            '
     767
    751768
    752769 END SUBROUTINE write_var_list
Note: See TracChangeset for help on using the changeset viewer.