Changeset 4423


Ignore:
Timestamp:
Feb 25, 2020 7:17:11 AM (4 years ago)
Author:
maronga
Message:

Switched back to serial NetCDF output for wind turbine output

File:
1 edited

Legend:

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

    r4420 r4423  
    2626! -----------------
    2727! $Id$
     28! Switched to serial output as data is aggerated before anyway.
     29!
     30! 4420 2020-02-24 14:13:56Z maronga
    2831! Added output control for wind turbine model
    2932!
     
    12821285
    12831286   
    1284     SUBROUTINE wtm_init_output
    1285    
    1286    
    1287         INTEGER(iwp) ::  ntimesteps               !< number of timesteps defined in NetCDF output file
    1288         INTEGER(iwp) ::  ntimesteps_max = 80000   !< number of maximum timesteps defined in NetCDF output file
    1289         INTEGER(iwp) ::  return_value             !< returned status value of called function
    1290        
    1291         INTEGER(iwp) ::  n  !< running index       
     1287SUBROUTINE wtm_init_output
     1288   
     1289   
     1290    INTEGER(iwp) ::  ntimesteps               !< number of timesteps defined in NetCDF output file
     1291    INTEGER(iwp) ::  ntimesteps_max = 80000   !< number of maximum timesteps defined in NetCDF output file
     1292    INTEGER(iwp) ::  return_value             !< returned status value of called function
     1293   
     1294    INTEGER(iwp) ::  n  !< running index       
    12921295     
    1293         INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ndim !< dummy to write dimension   
    1294        
    1295        
    1296 !
    1297 !--    Create NetCDF output file
    1298        nc_filename = 'DATA_1D_TS_WTM_NETCDF' // TRIM( coupling_char )     
    1299        return_value = dom_def_file( nc_filename, 'netcdf4-parallel' )
     1296    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ndim !< dummy to write dimension   
     1297       
     1298       
     1299!
     1300!-- Create NetCDF output file
     1301    nc_filename = 'DATA_1D_TS_WTM_NETCDF' // TRIM( coupling_char )     
     1302    return_value = dom_def_file( nc_filename, 'netcdf4-serial' )
    13001303                                                                         
    1301        ntimesteps = MIN( CEILING(                                                 &
    1302                      ( end_time - MAX( time_turbine_on, time_since_reference_point )&
    1303                      ) / MAX( 0.1_wp, dt_data_output_wtm ) ), ntimesteps_max )
    1304 
    1305        
     1304    ntimesteps = MIN( CEILING(                                                      &
     1305                    ( end_time - MAX( time_turbine_on, time_since_reference_point ) &
     1306                    ) / MAX( 0.1_wp, dt_data_output_wtm ) ), ntimesteps_max )
     1307
     1308     
     1309    IF ( myid == 0 )  THEN
    13061310!
    13071311!--    Define dimensions in output file
     
    15221526                                   attribute_name = 'units',           &
    15231527                                   value = 'degrees' ) 
    1524                                    
    1525     END SUBROUTINE
     1528
     1529   ENDIF   
     1530END SUBROUTINE
    15261531   
    15271532!------------------------------------------------------------------------------!
     
    31103115   
    31113116   
    3112        INTEGER(iwp)       ::  t_ind = 0       !< time index
     3117       INTEGER(iwp) ::  t_ind = 0       !< time index
    31133118   
    31143119       INTEGER(iwp) ::  return_value             !< returned status value of called function
    31153120   
    3116 !
    3117 !--    At the first call of this routine write the spatial coordinates.
    3118        IF ( .NOT. initial_write_coordinates )  THEN
     3121       IF ( myid == 0 ) THEN
     3122       
     3123!
     3124!--       At the first call of this routine write the spatial coordinates.
     3125          IF ( .NOT. initial_write_coordinates )  THEN
     3126             ALLOCATE ( output_values_1d_target(1:nturbines) )
     3127             output_values_1d_target = rcx(1:nturbines)
     3128             output_values_1d_pointer => output_values_1d_target     
     3129             return_value = dom_write_var( nc_filename,                              &
     3130                                        'x',                                         &
     3131                                        values_realwp_1d = output_values_1d_pointer, &
     3132                                        bounds_start = (/1/),                        &
     3133                                        bounds_end   = (/nturbines/) )
     3134
     3135             output_values_1d_target = rcy(1:nturbines)
     3136             output_values_1d_pointer => output_values_1d_target     
     3137             return_value = dom_write_var( nc_filename,                              &
     3138                                        'y',                                         &
     3139                                        values_realwp_1d = output_values_1d_pointer, &
     3140                                        bounds_start = (/1/),                        &
     3141                                        bounds_end   = (/nturbines/) )
     3142
     3143             output_values_1d_target = rcz(1:nturbines)
     3144             output_values_1d_pointer => output_values_1d_target     
     3145             return_value = dom_write_var( nc_filename,                              &
     3146                                        'z',                                         &
     3147                                        values_realwp_1d = output_values_1d_pointer, &
     3148                                        bounds_start = (/1/),                        &
     3149                                        bounds_end   = (/nturbines/) )                                       
     3150                                       
     3151             initial_write_coordinates = .TRUE.
     3152             DEALLOCATE ( output_values_1d_target )
     3153          ENDIF
     3154         
     3155          t_ind = t_ind + 1
     3156         
    31193157          ALLOCATE ( output_values_1d_target(1:nturbines) )
    3120           output_values_1d_target = rcx(1:nturbines)
    3121           output_values_1d_pointer => output_values_1d_target     
    3122           return_value = dom_write_var( nc_filename,                              &
    3123                                      'x',                                         &
    3124                                      values_realwp_1d = output_values_1d_pointer, &
    3125                                      bounds_start = (/1/),                        &
    3126                                      bounds_end   = (/nturbines/) )
    3127 
    3128           output_values_1d_target = rcy(1:nturbines)
    3129           output_values_1d_pointer => output_values_1d_target     
    3130           return_value = dom_write_var( nc_filename,                              &
    3131                                      'y',                                         &
    3132                                      values_realwp_1d = output_values_1d_pointer, &
    3133                                      bounds_start = (/1/),                        &
    3134                                      bounds_end   = (/nturbines/) )
    3135 
    3136           output_values_1d_target = rcz(1:nturbines)
    3137           output_values_1d_pointer => output_values_1d_target     
    3138           return_value = dom_write_var( nc_filename,                              &
    3139                                      'z',                                         &
    3140                                      values_realwp_1d = output_values_1d_pointer, &
    3141                                      bounds_start = (/1/),                        &
    3142                                      bounds_end   = (/nturbines/) )                                       
     3158          output_values_1d_target = omega_rot(:)
     3159          output_values_1d_pointer => output_values_1d_target
     3160         
     3161          return_value = dom_write_var( nc_filename,                                 &
     3162                                        'rotor_speed',                               &
     3163                                        values_realwp_1d = output_values_1d_pointer, &
     3164                                        bounds_start = (/1, t_ind/),                 &
     3165                                        bounds_end   = (/nturbines, t_ind /) )
     3166
     3167          output_values_1d_target = omega_gen(:)
     3168          output_values_1d_pointer => output_values_1d_target   
     3169          return_value = dom_write_var( nc_filename,                                 &
     3170                                        'generator_speed',                           &
     3171                                        values_realwp_1d = output_values_1d_pointer, &
     3172                                        bounds_start = (/1, t_ind/),                 &
     3173                                        bounds_end   = (/nturbines, t_ind /) )
     3174
     3175          output_values_1d_target = torque_gen_old(:)
     3176          output_values_1d_pointer => output_values_1d_target   
     3177
     3178          return_value = dom_write_var( nc_filename,                                 &
     3179                                        'generator_torque',                          &
     3180                                        values_realwp_1d = output_values_1d_pointer, &
     3181                                        bounds_start = (/1, t_ind/),                 &
     3182                                        bounds_end   = (/nturbines, t_ind /) )
     3183
     3184          output_values_1d_target = torque_total(:)
     3185          output_values_1d_pointer => output_values_1d_target   
     3186   
     3187          return_value = dom_write_var( nc_filename,                                 &
     3188                                        'rotor_torque',                              &
     3189                                        values_realwp_1d = output_values_1d_pointer, &
     3190                                        bounds_start = (/1, t_ind/),                 &
     3191                                        bounds_end   = (/nturbines, t_ind /) )
     3192
     3193          output_values_1d_target = pitch_add(:)
     3194          output_values_1d_pointer => output_values_1d_target   
     3195
     3196          return_value = dom_write_var( nc_filename,                                 &
     3197                                        'pitch_angle',                               &
     3198                                        values_realwp_1d = output_values_1d_pointer, &
     3199                                        bounds_start = (/1, t_ind/),                 &
     3200                                        bounds_end   = (/nturbines, t_ind /) )
     3201
     3202          output_values_1d_target = torque_gen_old(:)*omega_gen(:)*gen_eff
     3203          output_values_1d_pointer => output_values_1d_target   
     3204   
     3205          return_value = dom_write_var( nc_filename,                                 &
     3206                                        'generator_power',                           &
     3207                                        values_realwp_1d = output_values_1d_pointer, &
     3208                                        bounds_start = (/1, t_ind/),                 &
     3209                                        bounds_end   = (/nturbines, t_ind /) )
     3210
     3211          DO inot = 1, nturbines
     3212             output_values_1d_target(inot) = torque_total(inot)*omega_rot(inot)*air_dens
     3213          ENDDO
     3214          output_values_1d_pointer => output_values_1d_target   
    31433215                                       
    3144           initial_write_coordinates = .TRUE.
    3145           DEALLOCATE ( output_values_1d_target )
    3146        ENDIF
     3216          return_value = dom_write_var( nc_filename,                                 &
     3217                                        'rotor_power',                               &
     3218                                        values_realwp_1d = output_values_1d_pointer, &
     3219                                        bounds_start = (/1, t_ind/),                 &
     3220                                        bounds_end   = (/nturbines, t_ind /) )
     3221
     3222          output_values_1d_target = thrust_rotor(:)
     3223          output_values_1d_pointer => output_values_1d_target   
     3224   
     3225          return_value = dom_write_var( nc_filename,                                 &
     3226                                        'rotor_thrust',                              &
     3227                                        values_realwp_1d = output_values_1d_pointer, &
     3228                                        bounds_start = (/1, t_ind/),                 &
     3229                                        bounds_end   = (/nturbines, t_ind /) )
     3230
     3231          output_values_1d_target = wdir(:)*180.0_wp/pi
     3232          output_values_1d_pointer => output_values_1d_target   
    31473233         
    3148        t_ind = t_ind + 1
    3149          
    3150        ALLOCATE ( output_values_1d_target(1:nturbines) )
    3151        output_values_1d_target = omega_rot(:)
    3152        output_values_1d_pointer => output_values_1d_target
    3153          
    3154        return_value = dom_write_var( nc_filename,                                 &
    3155                                      'rotor_speed',                               &
    3156                                      values_realwp_1d = output_values_1d_pointer, &
    3157                                      bounds_start = (/1, t_ind/),                 &
    3158                                      bounds_end   = (/nturbines, t_ind /) )
    3159 
    3160        output_values_1d_target = omega_gen(:)
    3161        output_values_1d_pointer => output_values_1d_target   
    3162        return_value = dom_write_var( nc_filename,                                 &
    3163                                      'generator_speed',                           &
    3164                                      values_realwp_1d = output_values_1d_pointer, &
    3165                                      bounds_start = (/1, t_ind/),                 &
    3166                                      bounds_end   = (/nturbines, t_ind /) )
    3167 
    3168        output_values_1d_target = torque_gen_old(:)
    3169        output_values_1d_pointer => output_values_1d_target   
    3170 
    3171        return_value = dom_write_var( nc_filename,                                 &
    3172                                      'generator_torque',                          &
    3173                                      values_realwp_1d = output_values_1d_pointer, &
    3174                                      bounds_start = (/1, t_ind/),                 &
    3175                                      bounds_end   = (/nturbines, t_ind /) )
    3176 
    3177        output_values_1d_target = torque_total(:)
    3178        output_values_1d_pointer => output_values_1d_target   
    3179    
    3180        return_value = dom_write_var( nc_filename,                                 &
    3181                                      'rotor_torque',                              &
    3182                                      values_realwp_1d = output_values_1d_pointer, &
    3183                                      bounds_start = (/1, t_ind/),                 &
    3184                                      bounds_end   = (/nturbines, t_ind /) )
    3185 
    3186        output_values_1d_target = pitch_add(:)
    3187        output_values_1d_pointer => output_values_1d_target   
    3188 
    3189        return_value = dom_write_var( nc_filename,                                 &
    3190                                      'pitch_angle',                               &
    3191                                      values_realwp_1d = output_values_1d_pointer, &
    3192                                      bounds_start = (/1, t_ind/),                 &
    3193                                      bounds_end   = (/nturbines, t_ind /) )
    3194 
    3195        output_values_1d_target = torque_gen_old(:)*omega_gen(:)*gen_eff
    3196        output_values_1d_pointer => output_values_1d_target   
    3197    
    3198        return_value = dom_write_var( nc_filename,                                 &
    3199                                      'generator_power',                           &
    3200                                      values_realwp_1d = output_values_1d_pointer, &
    3201                                      bounds_start = (/1, t_ind/),                 &
    3202                                      bounds_end   = (/nturbines, t_ind /) )
    3203 
    3204        DO inot = 1, nturbines
    3205           output_values_1d_target(inot) = torque_total(inot)*omega_rot(inot)*air_dens
    3206        ENDDO
    3207        output_values_1d_pointer => output_values_1d_target   
    3208                                        
    3209        return_value = dom_write_var( nc_filename,                                 &
    3210                                      'rotor_power',                               &
    3211                                      values_realwp_1d = output_values_1d_pointer, &
    3212                                      bounds_start = (/1, t_ind/),                 &
    3213                                      bounds_end   = (/nturbines, t_ind /) )
    3214 
    3215        output_values_1d_target = thrust_rotor(:)
    3216        output_values_1d_pointer => output_values_1d_target   
    3217    
    3218        return_value = dom_write_var( nc_filename,                                 &
    3219                                      'rotor_thrust',                              &
    3220                                      values_realwp_1d = output_values_1d_pointer, &
    3221                                      bounds_start = (/1, t_ind/),                 &
    3222                                      bounds_end   = (/nturbines, t_ind /) )
    3223 
    3224        output_values_1d_target = wdir(:)*180.0_wp/pi
    3225        output_values_1d_pointer => output_values_1d_target   
    3226          
    3227        return_value = dom_write_var( nc_filename,                                 &
    3228                                      'wind_direction',                            &
    3229                                      values_realwp_1d = output_values_1d_pointer, &
    3230                                      bounds_start = (/1, t_ind/),                 &
    3231                                      bounds_end   = (/nturbines, t_ind /) )
    3232 
    3233        output_values_1d_target = (phi_yaw(:))*180.0_wp/pi
    3234        output_values_1d_pointer => output_values_1d_target   
    3235 
    3236        return_value = dom_write_var( nc_filename,                                 &
    3237                                      'yaw_angle',                                 &
    3238                                      values_realwp_1d = output_values_1d_pointer, &
    3239                                      bounds_start = (/1, t_ind/),                 &
    3240                                      bounds_end   = (/nturbines, t_ind /) )
    3241 
    3242        output_values_0d_target = time_since_reference_point
    3243        output_values_0d_pointer => output_values_0d_target
    3244    
    3245        return_value = dom_write_var( nc_filename,                                 &
    3246                                      'time',                                      &
    3247                                      values_realwp_0d = output_values_0d_pointer, &
    3248                                      bounds_start = (/t_ind/),                    &
     3234          return_value = dom_write_var( nc_filename,                                 &
     3235                                        'wind_direction',                            &
     3236                                        values_realwp_1d = output_values_1d_pointer, &
     3237                                        bounds_start = (/1, t_ind/),                 &
     3238                                        bounds_end   = (/nturbines, t_ind /) )
     3239
     3240          output_values_1d_target = (phi_yaw(:))*180.0_wp/pi
     3241          output_values_1d_pointer => output_values_1d_target   
     3242
     3243          return_value = dom_write_var( nc_filename,                                 &
     3244                                        'yaw_angle',                                 &
     3245                                        values_realwp_1d = output_values_1d_pointer, &
     3246                                        bounds_start = (/1, t_ind/),                 &
     3247                                        bounds_end   = (/nturbines, t_ind /) )
     3248
     3249          output_values_0d_target = time_since_reference_point
     3250          output_values_0d_pointer => output_values_0d_target
     3251   
     3252          return_value = dom_write_var( nc_filename,                                 &
     3253                                        'time',                                      &
     3254                                        values_realwp_0d = output_values_0d_pointer, &
     3255                                           bounds_start = (/t_ind/),                    &
    32493256                                     bounds_end   = (/t_ind/) )         
    32503257         
    3251        DEALLOCATE ( output_values_1d_target )
    3252        
     3258          DEALLOCATE ( output_values_1d_target )
     3259       
     3260       ENDIF
    32533261   
    32543262    END SUBROUTINE wtm_data_output
Note: See TracChangeset for help on using the changeset viewer.