Ignore:
Timestamp:
Feb 18, 2020 2:28:02 PM (4 years ago)
Author:
maronga
Message:

Added NetCDf output for wind turbine model. Added new features to palmrungui

File:
1 edited

Legend:

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

    r4360 r4411  
    88! version.
    99!
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
     10! PALM is distributed in the hope that it will be useful, but WITHOUT ANYr
    1111! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    1212! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     
    2626! -----------------
    2727! $Id$
     28! Added output in NetCDF format using DOM (only netcdf4-parallel is supported).
     29! Old ASCII output is still available at the moment.
     30!
     31! 4360 2020-01-07 11:25:50Z suehring
    2832! Introduction of wall_flags_total_0, which currently sets bits based on static
    2933! topography information used in wall_flags_static_0
     
    111115        ONLY:  coupling_char,                                                  &
    112116               debug_output,                                                   &
    113                dt_3d, dz, message_string, simulated_time,                      &
    114                wind_turbine, initializing_actions
     117               dt_3d, dz, end_time, message_string, time_since_reference_point,&
     118               wind_turbine, initializing_actions, origin_date_time
    115119
    116120    USE cpulog,                                                                &
    117121        ONLY:  cpu_log, log_point_s
    118122
     123    USE data_output_module
     124       
    119125    USE grid_variables,                                                        &
    120126        ONLY:  ddx, dx, ddy, dy
     
    133139    PRIVATE
    134140
     141   
     142   
     143    CHARACTER(LEN=100) ::  variable_name  !< name of output variable
     144    CHARACTER(LEN=30) :: nc_filename
     145   
    135146!
    136147!-- Variables specified in the namelist wind_turbine_par
     
    139150    INTEGER(iwp) ::  nturbines = 1   !< number of turbines
    140151
     152   
     153   
     154    REAL(wp), DIMENSION(:), POINTER   ::  output_values_1d_pointer !< pointer for 2d output array
     155    REAL(wp), POINTER                 ::  output_values_0d_pointer !< pointer for 2d output array 
     156    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET   ::  output_values_1d_target !< pointer for 2d output array
     157    REAL(wp), TARGET                ::  output_values_0d_target !< pointer for 2d output array     
     158   
    141159    LOGICAL ::  pitch_control = .FALSE.   !< switch for use of pitch controller
    142160    LOGICAL ::  speed_control = .FALSE.   !< switch for use of speed controller
    143161    LOGICAL ::  yaw_control   = .FALSE.   !< switch for use of yaw controller
    144162    LOGICAL ::  tl_cor        = .FALSE.    !< switch for use of tip loss correct.
    145 
     163   
     164    LOGICAL ::  initial_write_coordinates = .FALSE.
     165
     166    REAL(wp) ::  dt_wtm          = 1.0_wp
     167   
    146168    REAL(wp) ::  segment_length  = 1.0_wp          !< length of the segments, the rotor area is divided into
    147169                                                   !< (in tangential direction, as factor of MIN(dx,dy,dz))
     
    151173    REAL(wp) ::  tilt            = 0.0_wp          !< vertical tilt of the rotor [degree] ( positive = backwards )
    152174
     175
    153176    REAL(wp), DIMENSION(1:100) ::  dtow             = 0.0_wp  !< tower diameter [m]
    154     REAL(wp), DIMENSION(1:100) ::  omega_rot        = 0.9_wp  !< inital or constant rotor speed [rad/s]
     177    REAL(wp), DIMENSION(1:100), TARGET ::  omega_rot        = 0.9_wp  !< inital or constant rotor speed [rad/s]
    155178    REAL(wp), DIMENSION(1:100) ::  phi_yaw          = 0.0_wp  !< yaw angle [degree] ( clockwise, 0 = facing west )
    156179    REAL(wp), DIMENSION(1:100) ::  pitch_add        = 0.0_wp  !< constant pitch angle
     
    384407    END INTERFACE wtm_check_parameters
    385408
     409    INTERFACE wtm_data_output
     410       MODULE PROCEDURE wtm_data_output
     411    END INTERFACE wtm_data_output
     412   
    386413    INTERFACE wtm_init_arrays
    387414       MODULE PROCEDURE wtm_init_arrays
     
    392419    END INTERFACE wtm_init
    393420
     421    INTERFACE wtm_init_output
     422       MODULE PROCEDURE wtm_init_output
     423    END INTERFACE wtm_init_output
     424   
    394425    INTERFACE wtm_actions
    395426       MODULE PROCEDURE wtm_actions
     
    409440           wtm_parin,                                                          &
    410441           wtm_check_parameters,                                               &
     442           wtm_data_output,                                                    &
    411443           wtm_init_arrays,                                                    &
     444           wtm_init_output,                                                    &
    412445           wtm_init,                                                           &
    413446           wtm_actions,                                                        &
     
    878911       IMPLICIT NONE
    879912
     913       
     914 
    880915       INTEGER(iwp) ::  i  !< running index
    881916       INTEGER(iwp) ::  j  !< running index
    882917       INTEGER(iwp) ::  k  !< running index
    883918       
     919     
    884920!
    885921!--    Help variables for the smearing function       
     
    12551291       CALL wtm_read_blade_tables
    12561292
     1293       
     1294   
     1295       
     1296     
    12571297       IF ( debug_output )  CALL debug_message( 'wtm_init', 'end' )
    12581298 
     
    12601300
    12611301
     1302   
     1303    SUBROUTINE wtm_init_output
     1304   
     1305   
     1306        INTEGER(iwp) ::  ntimesteps               !< number of timesteps defined in NetCDF output file
     1307        INTEGER(iwp) ::  ntimesteps_max = 80000   !< number of maximum timesteps defined in NetCDF output file
     1308        INTEGER(iwp) ::  return_value             !< returned status value of called function
     1309       
     1310        INTEGER(iwp) ::  n  !< running index       
     1311     
     1312        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ndim !< dummy to write dimension   
     1313       
     1314       
     1315!
     1316!--    Create NetCDF output file
     1317       nc_filename = 'DATA_1D_TS_WTM_NETCDF' // TRIM( coupling_char )     
     1318       return_value = dom_def_file( nc_filename, 'netcdf4-parallel' )
     1319                                                                         
     1320       ntimesteps = MIN( CEILING(                                                 &
     1321                     ( end_time - MAX( time_turbine_on, time_since_reference_point )&
     1322                     ) / MAX( 0.1_wp, dt_wtm ) ), ntimesteps_max )
     1323
     1324       
     1325!
     1326!--    Define dimensions in output file
     1327       ALLOCATE( ndim(1:nturbines) )
     1328       DO  n = 1, nturbines
     1329          ndim(n) = n
     1330       ENDDO
     1331       return_value = dom_def_dim( nc_filename,                                &
     1332                                   dimension_name = 'turbine',                 &
     1333                                   output_type = 'int32',                      &
     1334                                   bounds = (/1_iwp, nturbines/),              &
     1335                                   values_int32 = ndim )
     1336       DEALLOCATE( ndim )
     1337
     1338       
     1339!
     1340!--    time
     1341       return_value = dom_def_dim( nc_filename,                                &
     1342                                   dimension_name = 'time',                   &
     1343                                   output_type = 'real32',                      &
     1344                                   bounds = (/1_iwp, ntimesteps/),             &
     1345                                   values_realwp = (/0.0_wp/) )   
     1346       
     1347 
     1348!
     1349!--    x
     1350       variable_name = 'x'
     1351       return_value = dom_def_var( nc_filename,                        &
     1352                                   variable_name = variable_name,              &
     1353                                   dimension_names = (/'turbine'/),            &
     1354                                   output_type = 'real32' )
     1355!
     1356!--    y
     1357       variable_name = 'y'
     1358       return_value = dom_def_var( nc_filename,                        &
     1359                                   variable_name = variable_name,              &
     1360                                   dimension_names = (/'turbine'/),            &
     1361                                   output_type = 'real32' )
     1362
     1363       variable_name = 'z'
     1364       return_value = dom_def_var( nc_filename,                        &
     1365                                   variable_name = variable_name,              &
     1366                                   dimension_names = (/'turbine'/),            &
     1367                                   output_type = 'real32' )
     1368                                   
     1369
     1370       return_value = dom_def_att( nc_filename,                        &
     1371                                   variable_name = 'time',                     &
     1372                                   attribute_name = 'units',                 &
     1373                                   value = 'seconds since ' // origin_date_time )
     1374                                   
     1375       return_value = dom_def_att( nc_filename,                        &
     1376                                   variable_name = 'x',                        &
     1377                                   attribute_name = 'units',                 &
     1378                                   value = 'm' )
     1379
     1380       return_value = dom_def_att( nc_filename,                        &
     1381                                   variable_name = 'y',                        &
     1382                                   attribute_name = 'units',                 &
     1383                                   value = 'm' )     
     1384
     1385       return_value = dom_def_att( nc_filename,                        &
     1386                                   variable_name = 'z',                        &
     1387                                   attribute_name = 'units',                 &
     1388                                   value = 'm' )                                   
     1389
     1390       return_value = dom_def_att( nc_filename,                        &
     1391                                   variable_name = 'x',                        &
     1392                                   attribute_name = 'long_name',                 &
     1393                                   value = 'x location of rotor center' )
     1394
     1395       return_value = dom_def_att( nc_filename,                        &
     1396                                   variable_name = 'y',                        &
     1397                                   attribute_name = 'long_name',                 &
     1398                                   value = 'y location of rotor center' )     
     1399
     1400       return_value = dom_def_att( nc_filename,                        &
     1401                                   variable_name = 'z',                        &
     1402                                   attribute_name = 'long_name',                 &
     1403                                   value = 'z location of rotor center' )     
     1404                                   
     1405                                   
     1406       return_value = dom_def_att( nc_filename,                        &
     1407                                   variable_name = 'turbine_name',             &
     1408                                   attribute_name = 'long_name',                 &
     1409                                   value = 'turbine name')   
     1410 
     1411       return_value = dom_def_att( nc_filename,                        &
     1412                                   variable_name = 'time',                     &
     1413                                   attribute_name = 'standard_name',             &
     1414                                   value = 'time')
     1415
     1416       return_value = dom_def_att( nc_filename,                        &
     1417                                   variable_name = 'time',                     &
     1418                                   attribute_name = 'axis',                    &
     1419                                   value = 'T')
     1420
     1421       return_value = dom_def_att( nc_filename,                        &
     1422                                   variable_name = 'x',                        &
     1423                                   attribute_name = 'axis',                    &
     1424                                   value = 'X' )
     1425
     1426       return_value = dom_def_att( nc_filename,                        &
     1427                                   variable_name = 'y',                        &
     1428                                   attribute_name = 'axis',                    &
     1429                                   value = 'Y' )                                 
     1430
     1431
     1432       variable_name = 'rotor_speed'
     1433       return_value = dom_def_var( nc_filename,                        &
     1434                                   variable_name = variable_name,      &
     1435                                   dimension_names = (/ 'turbine', 'time' /),     &
     1436                                   output_type = 'real32' )
     1437 
     1438       return_value = dom_def_att( nc_filename,                  &
     1439                                   variable_name = variable_name,        &
     1440                                   attribute_name = 'units',           &
     1441                                   value = 'rad/s' )
     1442 
     1443       variable_name = 'generator_speed'
     1444       return_value = dom_def_var( nc_filename,                        &
     1445                                   variable_name = variable_name,      &
     1446                                   dimension_names = (/ 'turbine', 'time' /),     &
     1447                                   output_type = 'real32' )
     1448 
     1449       return_value = dom_def_att( nc_filename,                  &
     1450                                   variable_name = variable_name,        &
     1451                                   attribute_name = 'units',           &
     1452                                   value = 'rad/s' )
     1453     
     1454     
     1455       variable_name = 'generator_torque'
     1456       return_value = dom_def_var( nc_filename,                        &
     1457                                   variable_name = variable_name,      &
     1458                                   dimension_names = (/ 'turbine', 'time' /),     &
     1459                                   output_type = 'real32' )
     1460 
     1461       return_value = dom_def_att( nc_filename,                  &
     1462                                   variable_name = variable_name,        &
     1463                                   attribute_name = 'units',           &
     1464                                   value = 'Nm' ) 
     1465       
     1466       variable_name = 'rotor_torque'
     1467       return_value = dom_def_var( nc_filename,                        &
     1468                                   variable_name = variable_name,      &
     1469                                   dimension_names = (/ 'turbine', 'time' /),     &
     1470                                   output_type = 'real32' )
     1471 
     1472       return_value = dom_def_att( nc_filename,                  &
     1473                                   variable_name = variable_name,        &
     1474                                   attribute_name = 'units',           &
     1475                                   value = 'Nm' )
     1476
     1477       variable_name = 'pitch_angle'
     1478       return_value = dom_def_var( nc_filename,                        &
     1479                                   variable_name = variable_name,      &
     1480                                   dimension_names = (/ 'turbine', 'time' /),     &
     1481                                   output_type = 'real32' )
     1482 
     1483       return_value = dom_def_att( nc_filename,                  &
     1484                                   variable_name = variable_name,        &
     1485                                   attribute_name = 'units',           &
     1486                                   value = 'degrees' )     
     1487                                   
     1488       variable_name = 'generator_power'
     1489       return_value = dom_def_var( nc_filename,                        &
     1490                                   variable_name = variable_name,      &
     1491                                   dimension_names = (/ 'turbine', 'time' /),     &
     1492                                   output_type = 'real32' )
     1493 
     1494       return_value = dom_def_att( nc_filename,                  &
     1495                                   variable_name = variable_name,        &
     1496                                   attribute_name = 'units',           &
     1497                                   value = 'W' ) 
     1498                                   
     1499       variable_name = 'rotor_power'
     1500       return_value = dom_def_var( nc_filename,                        &
     1501                                   variable_name = variable_name,      &
     1502                                   dimension_names = (/ 'turbine', 'time' /),     &
     1503                                   output_type = 'real32' )
     1504 
     1505       return_value = dom_def_att( nc_filename,                  &
     1506                                   variable_name = variable_name,        &
     1507                                   attribute_name = 'units',           &
     1508                                   value = 'W' ) 
     1509                                   
     1510        variable_name = 'rotor_thrust'
     1511       return_value = dom_def_var( nc_filename,                        &
     1512                                   variable_name = variable_name,      &
     1513                                   dimension_names = (/ 'turbine', 'time' /),     &
     1514                                   output_type = 'real32' )
     1515 
     1516       return_value = dom_def_att( nc_filename,                  &
     1517                                   variable_name = variable_name,        &
     1518                                   attribute_name = 'units',           &
     1519                                   value = 'N' )   
     1520                                   
     1521                                   
     1522       variable_name = 'wind_direction'
     1523       return_value = dom_def_var( nc_filename,                        &
     1524                                   variable_name = variable_name,      &
     1525                                   dimension_names = (/ 'turbine', 'time' /),     &
     1526                                   output_type = 'real32' )
     1527 
     1528       return_value = dom_def_att( nc_filename,                  &
     1529                                   variable_name = variable_name,        &
     1530                                   attribute_name = 'units',           &
     1531                                   value = 'degrees' ) 
     1532                                   
     1533       variable_name = 'yaw_angle'
     1534       return_value = dom_def_var( nc_filename,                        &
     1535                                   variable_name = variable_name,      &
     1536                                   dimension_names = (/ 'turbine', 'time' /),     &
     1537                                   output_type = 'real32' )
     1538 
     1539       return_value = dom_def_att( nc_filename,                  &
     1540                                   variable_name = variable_name,        &
     1541                                   attribute_name = 'units',           &
     1542                                   value = 'degrees' ) 
     1543                                   
     1544    END SUBROUTINE
     1545   
    12621546!------------------------------------------------------------------------------!
    12631547! Description:
     
    15951879       INTEGER(iwp) ::  ring             !<
    15961880       INTEGER(iwp) ::  ii, jj, kk       !<
    1597    
     1881       
    15981882       REAL(wp)     ::  flag               !< flag to mask topography grid points
    15991883       REAL(wp)     ::  sin_rot, cos_rot   !<
     
    16041888       
    16051889       REAL(wp) ::  dist_u_3d, dist_v_3d, dist_w_3d  !< smearing distances
    1606 
     1890     
    16071891       
    16081892!
     
    16191903
    16201904
    1621        IF ( simulated_time >= time_turbine_on ) THEN
     1905       IF ( time_since_reference_point >= time_turbine_on ) THEN
    16221906
    16231907!
     
    23992683          ENDIF
    24002684
     2685         
     2686         
     2687         
    24012688          DO inot = 1, nturbines
    24022689
     2690
     2691         
    24032692             IF ( myid == 0 ) THEN
    24042693                IF ( openfile_turb_mod(400+inot)%opened )  THEN
    2405                    WRITE ( 400+inot, 106 ) simulated_time, omega_rot(inot),    &
     2694                   WRITE ( 400+inot, 106 ) time_since_reference_point, omega_rot(inot),    &
    24062695                             omega_gen(inot), torque_gen_old(inot),            &
    24072696                             torque_total(inot), pitch_add(inot),              &
     
    24192708                                           turbine_id ), FORM='FORMATTED' )
    24202709                   WRITE ( 400+inot, 105 ) inot
    2421                    WRITE ( 400+inot, 106 ) simulated_time, omega_rot(inot),    &
     2710                   WRITE ( 400+inot, 106 ) time_since_reference_point, omega_rot(inot),    &
    24222711                             omega_gen(inot), torque_gen_old(inot),            &
    24232712                             torque_total(inot), pitch_add(inot),              &
     
    24342723          ENDDO                                    !-- end of loop over turbines
    24352724
    2436        ENDIF
    2437 
     2725         
     2726         
     2727       ENDIF   
     2728
     2729
     2730!
     2731!--    NetCDF output, should be moved
     2732       CALL wtm_data_output
     2733       
    24382734       CALL cpu_log( log_point_s(61), 'wtm_forces', 'stop' )
    24392735       
     
    24492745                   F12.1,1X,F12.1,4X,F7.2,4X,F7.2)
    24502746
    2451 
     2747           
     2748                   
    24522749    END SUBROUTINE wtm_forces
    24532750
     
    26922989!
    26932990!--       Apply the x-component of the force to the u-component of the flow:
    2694           IF ( simulated_time >= time_turbine_on )  THEN
     2991          IF ( time_since_reference_point >= time_turbine_on )  THEN
    26952992             DO  i = nxlg, nxrg
    26962993                DO  j = nysg, nyng
     
    27153012!
    27163013!--       Apply the y-component of the force to the v-component of the flow:
    2717           IF ( simulated_time >= time_turbine_on )  THEN
     3014          IF ( time_since_reference_point >= time_turbine_on )  THEN
    27183015             DO  i = nxlg, nxrg
    27193016                DO  j = nysg, nyng
     
    27353032!
    27363033!--       Apply the z-component of the force to the w-component of the flow:
    2737           IF ( simulated_time >= time_turbine_on )  THEN
     3034          IF ( time_since_reference_point >= time_turbine_on )  THEN
    27383035             DO  i = nxlg, nxrg
    27393036                DO  j = nysg, nyng
     
    27813078!
    27823079!--       Apply the x-component of the force to the u-component of the flow:
    2783           IF ( simulated_time >= time_turbine_on )  THEN
     3080          IF ( time_since_reference_point >= time_turbine_on )  THEN
    27843081             DO  k = nzb+1,  MAXVAL(k_hub) + MAXVAL(k_smear)
    27853082!
     
    27993096!
    28003097!--       Apply the y-component of the force to the v-component of the flow:
    2801           IF ( simulated_time >= time_turbine_on )  THEN
     3098          IF ( time_since_reference_point >= time_turbine_on )  THEN
    28023099             DO  k = nzb+1,  MAXVAL(k_hub) + MAXVAL(k_smear)
    28033100                tend_nac_y = 0.5_wp * nac_cd_surf(k,j,i) *                     &
     
    28153112!
    28163113!--       Apply the z-component of the force to the w-component of the flow:
    2817           IF ( simulated_time >= time_turbine_on )  THEN
     3114          IF ( time_since_reference_point >= time_turbine_on )  THEN
    28183115             DO  k = nzb+1,  MAXVAL(k_hub) + MAXVAL(k_smear)
    28193116                tend(k,j,i) = tend(k,j,i) - rot_tend_z(k,j,i)                  &
     
    28323129    END SUBROUTINE wtm_actions_ij
    28333130
     3131   
     3132    SUBROUTINE wtm_data_output
     3133   
     3134   
     3135       INTEGER(iwp)       ::  t_ind = 0       !< time index
     3136   
     3137       INTEGER(iwp) ::  return_value             !< returned status value of called function
     3138   
     3139!
     3140!--    At the first call of this routine write the spatial coordinates.
     3141       IF ( .NOT. initial_write_coordinates )  THEN
     3142          ALLOCATE ( output_values_1d_target(1:nturbines) )
     3143          output_values_1d_target = rcx(1:nturbines)
     3144          output_values_1d_pointer => output_values_1d_target     
     3145          return_value = dom_write_var( nc_filename,                              &
     3146                                     'x',                                         &
     3147                                     values_realwp_1d = output_values_1d_pointer, &
     3148                                     bounds_start = (/1/),                        &
     3149                                     bounds_end   = (/nturbines/) )
     3150
     3151          output_values_1d_target = rcy(1:nturbines)
     3152          output_values_1d_pointer => output_values_1d_target     
     3153          return_value = dom_write_var( nc_filename,                              &
     3154                                     'y',                                         &
     3155                                     values_realwp_1d = output_values_1d_pointer, &
     3156                                     bounds_start = (/1/),                        &
     3157                                     bounds_end   = (/nturbines/) )
     3158
     3159          output_values_1d_target = rcz(1:nturbines)
     3160          output_values_1d_pointer => output_values_1d_target     
     3161          return_value = dom_write_var( nc_filename,                              &
     3162                                     'z',                                         &
     3163                                     values_realwp_1d = output_values_1d_pointer, &
     3164                                     bounds_start = (/1/),                        &
     3165                                     bounds_end   = (/nturbines/) )                                       
     3166                                       
     3167          initial_write_coordinates = .TRUE.
     3168          DEALLOCATE ( output_values_1d_target )
     3169       ENDIF
     3170         
     3171       t_ind = t_ind + 1
     3172         
     3173       ALLOCATE ( output_values_1d_target(1:nturbines) )
     3174       output_values_1d_target = omega_rot(:)
     3175       output_values_1d_pointer => output_values_1d_target
     3176         
     3177       return_value = dom_write_var( nc_filename,                                 &
     3178                                     'rotor_speed',                               &
     3179                                     values_realwp_1d = output_values_1d_pointer, &
     3180                                     bounds_start = (/1, t_ind/),                 &
     3181                                     bounds_end   = (/nturbines, t_ind /) )
     3182
     3183       output_values_1d_target = omega_gen(:)
     3184       output_values_1d_pointer => output_values_1d_target   
     3185       return_value = dom_write_var( nc_filename,                                 &
     3186                                     'generator_speed',                           &
     3187                                     values_realwp_1d = output_values_1d_pointer, &
     3188                                     bounds_start = (/1, t_ind/),                 &
     3189                                     bounds_end   = (/nturbines, t_ind /) )
     3190
     3191       output_values_1d_target = torque_gen_old(:)
     3192       output_values_1d_pointer => output_values_1d_target   
     3193
     3194       return_value = dom_write_var( nc_filename,                                 &
     3195                                     'generator_torque',                          &
     3196                                     values_realwp_1d = output_values_1d_pointer, &
     3197                                     bounds_start = (/1, t_ind/),                 &
     3198                                     bounds_end   = (/nturbines, t_ind /) )
     3199
     3200       output_values_1d_target = torque_total(:)
     3201       output_values_1d_pointer => output_values_1d_target   
     3202   
     3203       return_value = dom_write_var( nc_filename,                                 &
     3204                                     'rotor_torque',                              &
     3205                                     values_realwp_1d = output_values_1d_pointer, &
     3206                                     bounds_start = (/1, t_ind/),                 &
     3207                                     bounds_end   = (/nturbines, t_ind /) )
     3208
     3209       output_values_1d_target = pitch_add(:)
     3210       output_values_1d_pointer => output_values_1d_target   
     3211
     3212       return_value = dom_write_var( nc_filename,                                 &
     3213                                     'pitch_angle',                               &
     3214                                     values_realwp_1d = output_values_1d_pointer, &
     3215                                     bounds_start = (/1, t_ind/),                 &
     3216                                     bounds_end   = (/nturbines, t_ind /) )
     3217
     3218       output_values_1d_target = torque_gen_old(:)*omega_gen(:)*gen_eff
     3219       output_values_1d_pointer => output_values_1d_target   
     3220   
     3221       return_value = dom_write_var( nc_filename,                                 &
     3222                                     'generator_power',                           &
     3223                                     values_realwp_1d = output_values_1d_pointer, &
     3224                                     bounds_start = (/1, t_ind/),                 &
     3225                                     bounds_end   = (/nturbines, t_ind /) )
     3226
     3227       DO inot = 1, nturbines
     3228          output_values_1d_target(inot) = torque_total(inot)*omega_rot(inot)*air_dens
     3229       ENDDO
     3230       output_values_1d_pointer => output_values_1d_target   
     3231                                       
     3232       return_value = dom_write_var( nc_filename,                                 &
     3233                                     'rotor_power',                               &
     3234                                     values_realwp_1d = output_values_1d_pointer, &
     3235                                     bounds_start = (/1, t_ind/),                 &
     3236                                     bounds_end   = (/nturbines, t_ind /) )
     3237
     3238       output_values_1d_target = thrust_rotor(:)
     3239       output_values_1d_pointer => output_values_1d_target   
     3240   
     3241       return_value = dom_write_var( nc_filename,                                 &
     3242                                     'rotor_thrust',                              &
     3243                                     values_realwp_1d = output_values_1d_pointer, &
     3244                                     bounds_start = (/1, t_ind/),                 &
     3245                                     bounds_end   = (/nturbines, t_ind /) )
     3246
     3247       output_values_1d_target = wdir(:)*180.0_wp/pi
     3248       output_values_1d_pointer => output_values_1d_target   
     3249         
     3250       return_value = dom_write_var( nc_filename,                                 &
     3251                                     'wind_direction',                            &
     3252                                     values_realwp_1d = output_values_1d_pointer, &
     3253                                     bounds_start = (/1, t_ind/),                 &
     3254                                     bounds_end   = (/nturbines, t_ind /) )
     3255
     3256       output_values_1d_target = (phi_yaw(:))*180.0_wp/pi
     3257       output_values_1d_pointer => output_values_1d_target   
     3258
     3259       return_value = dom_write_var( nc_filename,                                 &
     3260                                     'yaw_angle',                                 &
     3261                                     values_realwp_1d = output_values_1d_pointer, &
     3262                                     bounds_start = (/1, t_ind/),                 &
     3263                                     bounds_end   = (/nturbines, t_ind /) )
     3264
     3265       output_values_0d_target = time_since_reference_point
     3266       output_values_0d_pointer => output_values_0d_target
     3267   
     3268       return_value = dom_write_var( nc_filename,                                 &
     3269                                     'time',                                      &
     3270                                     values_realwp_0d = output_values_0d_pointer, &
     3271                                     bounds_start = (/t_ind/),                    &
     3272                                     bounds_end   = (/t_ind/) )         
     3273         
     3274       DEALLOCATE ( output_values_1d_target )
     3275       
     3276   
     3277    END SUBROUTINE wtm_data_output
     3278   
    28343279 END MODULE wind_turbine_model_mod
Note: See TracChangeset for help on using the changeset viewer.