Ignore:
Timestamp:
Feb 7, 2019 10:11:02 AM (5 years ago)
Author:
raasch
Message:

modifications to avoid compiler warnings about unused variables, temperton-fft: GOTO statements replaced, file re-formatted corresponding to coding standards, ssh-calls for compilations on remote systems modified to avoid output of login messages on specific systems changed again (palmbuild, reverted as before r3549), error messages for failed restarts extended (palmrun)

File:
1 edited

Legend:

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

    r3685 r3725  
    2626! -----------------
    2727! $Id$
     28! unused variables removed
     29!
     30! 3685 2019-01-21 01:02:11Z knoop
    2831! Some interface calls moved to module_interface + cleanup
    2932!
     
    237240    REAL(wp), DIMENSION(1:100) ::  rnac             = 0.0_wp  !< nacelle diameter [m]
    238241    REAL(wp), DIMENSION(1:100) ::  rr              = 63.0_wp  !< rotor radius [m]
    239     REAL(wp), DIMENSION(1:100) ::  turb_cd_nacelle = 0.85_wp  !< drag coefficient for nacelle
     242!    REAL(wp), DIMENSION(1:100) ::  turb_cd_nacelle = 0.85_wp  !< drag coefficient for nacelle
    240243    REAL(wp), DIMENSION(1:100) ::  turb_cd_tower    = 1.2_wp  !< drag coefficient for tower
    241244
     
    306309    REAL(wp) ::  eps_min          !<
    307310    REAL(wp) ::  eps_min2         !<
    308     REAL(wp) ::  sqrt_arg         !<
    309311
    310312!
     
    519521       IMPLICIT NONE
    520522       
    521        INTEGER(iwp) ::  ierrn       !<
    522 
    523523       CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    524524
     
    531531                                  rnac, rr, segment_length, segment_width,     &
    532532                                  slope2, speed_control, tilt, time_turbine_on,&
    533                                   turb_cd_nacelle, turb_cd_tower, pitch_rate,  &
     533                                  turb_cd_tower, pitch_rate,                   &
    534534                                  yaw_control, yaw_speed, tl_cor
     535!                                  , turb_cd_nacelle
    535536                                 
    536537       NAMELIST /wind_turbine_parameters/                                      &
     
    543544                                  rnac, rr, segment_length, segment_width,     &
    544545                                  slope2, speed_control, tilt, time_turbine_on,&
    545                                   turb_cd_nacelle, turb_cd_tower, pitch_rate,  &
     546                                  turb_cd_tower, pitch_rate,                   &
    546547                                  yaw_control, yaw_speed, tl_cor
     548!                                  , turb_cd_nacelle
    547549!
    548550!--    Try to find wind turbine model package
     
    980982       INTEGER(iwp) ::  tower_n      !<
    981983       INTEGER(iwp) ::  tower_s      !<
    982 !
    983 !--    Help variables for the calulaction of the nacelle drag
    984        INTEGER(iwp) ::  i_ip         !<
    985        INTEGER(iwp) ::  i_ipg        !<
    986        
    987        REAL(wp) ::  yvalue               
    988        REAL(wp) ::  dy_int           !<
    989        REAL(wp) ::  dz_int           !<
    990984       
    991985       REAL(wp), DIMENSION(:,:), ALLOCATABLE :: circle_points  !<
Note: See TracChangeset for help on using the changeset viewer.