Changeset 2669 for palm/trunk/SOURCE


Ignore:
Timestamp:
Dec 6, 2017 4:03:27 PM (6 years ago)
Author:
raasch
Message:

file attributes and activation strings in .palm.iofiles revised, file extensions for nesting, masked output, wind turbine data, etc. changed

Location:
palm/trunk/SOURCE
Files:
8 edited

Legend:

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

    r2516 r2669  
    2525! -----------------
    2626! $Id$
     27! file name extension for masked data files is changed to "_M##" and is now
     28! appended at the end of the filename,
     29! file ids not used any more have been removed
     30!
     31! 2516 2017-10-04 11:03:04Z suehring
    2732! Remove tabs
    2833!
     
    184189    IMPLICIT NONE
    185190
    186     CHARACTER (LEN=2)   ::  mask_char               !<
     191    CHARACTER (LEN=4)   ::  mask_char               !<
    187192    CHARACTER (LEN=2)   ::  suffix                  !<
    188193    CHARACTER (LEN=30)  ::  filename                !<
     
    209214    IF ( openfile(file_id)%opened_before )  THEN
    210215       SELECT CASE ( file_id )
    211           CASE ( 13, 14, 21, 22, 23, 80:85, 117 )
     216          CASE ( 13, 14, 21, 22, 23, 80, 85, 117 )
    212217             IF ( file_id == 14 .AND. openfile(file_id)%opened_before )  THEN
    213218                message_string = 're-open of unit ' //                         &
     
    230235    SELECT CASE ( file_id )
    231236
    232        CASE ( 15, 16, 17, 18, 19, 50:59, 81:84, 104:105, 107, 109, 117 )
     237       CASE ( 15, 16, 17, 18, 19, 50:59, 104:105, 107, 109, 117 )
    233238     
    234239          IF ( myid /= 0 )  THEN
     
    260265          ENDIF
    261266
    262        CASE ( 27, 28, 29, 31, 33, 71:73, 90:99 )
     267       CASE ( 90:99 )
    263268
    264269!
     
    479484          ENDIF
    480485
    481        CASE ( 81 )
    482 
    483              OPEN ( 81, FILE='PLOTSP_X_PAR'//TRIM( coupling_char ),            &
    484                         FORM='FORMATTED', DELIM='APOSTROPHE', RECL=1500,       &
    485                         POSITION='APPEND' )
    486 
    487        CASE ( 82 )
    488 
    489              OPEN ( 82, FILE='PLOTSP_X_DATA'//TRIM( coupling_char ),           &
    490                         FORM='FORMATTED', POSITION = 'APPEND' )
    491 
    492        CASE ( 83 )
    493 
    494              OPEN ( 83, FILE='PLOTSP_Y_PAR'//TRIM( coupling_char ),            &
    495                         FORM='FORMATTED', DELIM='APOSTROPHE', RECL=1500,       &
    496                         POSITION='APPEND' )
    497 
    498        CASE ( 84 )
    499 
    500              OPEN ( 84, FILE='PLOTSP_Y_DATA'//TRIM( coupling_char ),           &
    501                         FORM='FORMATTED', POSITION='APPEND' )
    502 
    503486       CASE ( 85 )
    504487
     
    10781061          IF ( file_id <= 200+max_masks )  THEN
    10791062             mid = file_id - 200
    1080              WRITE ( mask_char,'(I2.2)') mid
    1081              filename = 'DATA_MASK_' // mask_char // '_NETCDF' //              &
    1082                         TRIM( coupling_char )
     1063             WRITE ( mask_char,'(A2,I2.2)')  '_M', mid
     1064             filename = 'DATA_MASK_NETCDF' // TRIM( coupling_char ) //         &
     1065                        mask_char
    10831066             av = 0
    10841067          ELSE
    10851068             mid = file_id - (200+max_masks)
    1086              WRITE ( mask_char,'(I2.2)') mid
    1087              filename = 'DATA_MASK_' // mask_char // '_AV_NETCDF' //           &
    1088                         TRIM( coupling_char )
     1069             WRITE ( mask_char,'(A2,I2.2)')  '_M', mid
     1070             filename = 'DATA_MASK_AV_NETCDF' // TRIM( coupling_char ) //      &
     1071                        mask_char
    10891072             av = 1
    10901073          ENDIF
  • palm/trunk/SOURCE/check_parameters.f90

    r2628 r2669  
    2525! -----------------
    2626! $Id$
     27! mrun-string replaced by palmrun
     28!
     29! 2628 2017-11-20 12:40:38Z schwenkel
    2730! Enabled particle advection with grid stretching -> Removed parameter check
    2831!
     
    10221025!--    ocean run (this setting is done via mrun-option -y)
    10231026       message_string = 'ocean = .F. does not allow coupling_char = "' //      &
    1024                         TRIM( coupling_char ) // '" set by mrun-option "-y"'
     1027                        TRIM( coupling_char ) // '" set by palmrun-option "-y"'
    10251028       CALL message( 'check_parameters', 'PA0317', 1, 2, 0, 6, 0 )
    10261029
  • palm/trunk/SOURCE/init_coupling.f90

    r2365 r2669  
    2525! ------------------
    2626! $Id$
     27! file extension for vertical nesting changed to "_NV"
     28!
     29! 2365 2017-08-21 14:59:59Z kanani
    2730! Vertical nesting implemented (SadiqHuq)
    2831!
     
    192195!
    193196!-- Set file extension for vertical nesting
    194        coupling_char = '_N'
     197       coupling_char = '_NV'
    195198    ENDIF
    196199
  • palm/trunk/SOURCE/modules.f90

    r2575 r2669  
    2525! -----------------
    2626! $Id$
     27! CONTIGUOUS-attribut added to 3d pointer arrays,
     28! coupling_char extended to LEN=8
     29!
     30! 2575 2017-10-24 09:57:58Z maronga
    2731! Renamed phi -> latitude, moved longitude from radiation model to modules
    2832!
     
    776780    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w_3     !< pointer for swapping of timelevels for respective quantity
    777781
    778     REAL(wp), DIMENSION(:,:,:), POINTER ::  e          !< pointer: subgrid-scale turbulence kinetic energy (sgs tke)
    779     REAL(wp), DIMENSION(:,:,:), POINTER ::  e_p        !< pointer: prognostic value of sgs tke
    780     REAL(wp), DIMENSION(:,:,:), POINTER ::  nc         !< pointer: cloud drop number density
    781     REAL(wp), DIMENSION(:,:,:), POINTER ::  nc_p       !< pointer: prognostic value of cloud drop number density
    782     REAL(wp), DIMENSION(:,:,:), POINTER ::  nr         !< pointer: rain drop number density
    783     REAL(wp), DIMENSION(:,:,:), POINTER ::  nr_p       !< pointer: prognostic value of rain drop number density
    784     REAL(wp), DIMENSION(:,:,:), POINTER ::  prho       !< pointer: potential density
    785     REAL(wp), DIMENSION(:,:,:), POINTER ::  pt         !< pointer: potential temperature
    786     REAL(wp), DIMENSION(:,:,:), POINTER ::  pt_p       !< pointer: prognostic value of potential temperature
    787     REAL(wp), DIMENSION(:,:,:), POINTER ::  q          !< pointer: specific humidity
    788     REAL(wp), DIMENSION(:,:,:), POINTER ::  q_p        !< pointer: prognostic value of specific humidity
    789     REAL(wp), DIMENSION(:,:,:), POINTER ::  qc         !< pointer: cloud water content
    790     REAL(wp), DIMENSION(:,:,:), POINTER ::  qc_p       !< pointer: cloud water content
    791     REAL(wp), DIMENSION(:,:,:), POINTER ::  ql         !< pointer: liquid water content
    792     REAL(wp), DIMENSION(:,:,:), POINTER ::  ql_c       !< pointer: change in liquid water content due to
    793                                                        !< condensation/evaporation during last time step
    794     REAL(wp), DIMENSION(:,:,:), POINTER ::  qr         !< pointer: rain water content
    795     REAL(wp), DIMENSION(:,:,:), POINTER ::  qr_p       !< pointer: prognostic value of rain water content
    796     REAL(wp), DIMENSION(:,:,:), POINTER ::  rho_ocean  !< pointer: density of ocean
    797     REAL(wp), DIMENSION(:,:,:), POINTER ::  s          !< pointer: passive scalar
    798     REAL(wp), DIMENSION(:,:,:), POINTER ::  s_p        !< pointer: prognostic value of passive scalar
    799     REAL(wp), DIMENSION(:,:,:), POINTER ::  sa         !< pointer: ocean salinity
    800     REAL(wp), DIMENSION(:,:,:), POINTER ::  sa_p       !< pointer: prognostic value of ocean salinity
    801     REAL(wp), DIMENSION(:,:,:), POINTER ::  te_m       !< pointer: weighted tendency of e for previous sub-timestep (Runge-Kutta)
    802     REAL(wp), DIMENSION(:,:,:), POINTER ::  tnc_m      !< pointer: weighted tendency of nc for previous sub-timestep (Runge-Kutta)
    803     REAL(wp), DIMENSION(:,:,:), POINTER ::  tnr_m      !< pointer: weighted tendency of nr for previous sub-timestep (Runge-Kutta)
    804     REAL(wp), DIMENSION(:,:,:), POINTER ::  tpt_m      !< pointer: weighted tendency of pt for previous sub-timestep (Runge-Kutta)
    805     REAL(wp), DIMENSION(:,:,:), POINTER ::  tq_m       !< pointer: weighted tendency of q for previous sub-timestep (Runge-Kutta)
    806     REAL(wp), DIMENSION(:,:,:), POINTER ::  tqc_m      !< pointer: weighted tendency of qc for previous sub-timestep (Runge-Kutta)
    807     REAL(wp), DIMENSION(:,:,:), POINTER ::  tqr_m      !< pointer: weighted tendency of qr for previous sub-timestep (Runge-Kutta)
    808     REAL(wp), DIMENSION(:,:,:), POINTER ::  ts_m       !< pointer: weighted tendency of s for previous sub-timestep (Runge-Kutta)
    809     REAL(wp), DIMENSION(:,:,:), POINTER ::  tsa_m      !< pointer: weighted tendency of sa for previous sub-timestep (Runge-Kutta)
    810     REAL(wp), DIMENSION(:,:,:), POINTER ::  tu_m       !< pointer: weighted tendency of u for previous sub-timestep (Runge-Kutta)
    811     REAL(wp), DIMENSION(:,:,:), POINTER ::  tv_m       !< pointer: weighted tendency of v for previous sub-timestep (Runge-Kutta)
    812     REAL(wp), DIMENSION(:,:,:), POINTER ::  tw_m       !< pointer: weighted tendency of w for previous sub-timestep (Runge-Kutta)
    813     REAL(wp), DIMENSION(:,:,:), POINTER ::  u          !< pointer: horizontal velocity component u (x-direction)
    814     REAL(wp), DIMENSION(:,:,:), POINTER ::  u_p        !< pointer: prognostic value of u
    815     REAL(wp), DIMENSION(:,:,:), POINTER ::  v          !< pointer: horizontal velocity component v (y-direction)
    816     REAL(wp), DIMENSION(:,:,:), POINTER ::  v_p        !< pointer: prognostic value of v
    817     REAL(wp), DIMENSION(:,:,:), POINTER ::  vpt        !< pointer: virtual potential temperature
    818     REAL(wp), DIMENSION(:,:,:), POINTER ::  w          !< pointer: vertical velocity component w (z-direction)
    819     REAL(wp), DIMENSION(:,:,:), POINTER ::  w_p        !< pointer: prognostic value of w
     782    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  e          !< pointer: subgrid-scale turbulence kinetic energy (sgs tke)
     783    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  e_p        !< pointer: prognostic value of sgs tke
     784    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nc         !< pointer: cloud drop number density
     785    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nc_p       !< pointer: prognostic value of cloud drop number density
     786    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nr         !< pointer: rain drop number density
     787    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nr_p       !< pointer: prognostic value of rain drop number density
     788    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  prho       !< pointer: potential density
     789    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  pt         !< pointer: potential temperature
     790    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  pt_p       !< pointer: prognostic value of potential temperature
     791    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  q          !< pointer: specific humidity
     792    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  q_p        !< pointer: prognostic value of specific humidity
     793    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qc         !< pointer: cloud water content
     794    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qc_p       !< pointer: cloud water content
     795    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ql         !< pointer: liquid water content
     796    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ql_c       !< pointer: change in liquid water content due to
     797                                                                   !< condensation/evaporation during last time step
     798    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qr         !< pointer: rain water content
     799    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qr_p       !< pointer: prognostic value of rain water content
     800    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  rho_ocean  !< pointer: density of ocean
     801    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  s          !< pointer: passive scalar
     802    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  s_p        !< pointer: prognostic value of passive scalar
     803    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  sa         !< pointer: ocean salinity
     804    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  sa_p       !< pointer: prognostic value of ocean salinity
     805    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  te_m       !< pointer: weighted tendency of e for previous sub-timestep (Runge-Kutta)
     806    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnc_m      !< pointer: weighted tendency of nc for previous sub-timestep (Runge-Kutta)
     807    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnr_m      !< pointer: weighted tendency of nr for previous sub-timestep (Runge-Kutta)
     808    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tpt_m      !< pointer: weighted tendency of pt for previous sub-timestep (Runge-Kutta)
     809    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tq_m       !< pointer: weighted tendency of q for previous sub-timestep (Runge-Kutta)
     810    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqc_m      !< pointer: weighted tendency of qc for previous sub-timestep (Runge-Kutta)
     811    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqr_m      !< pointer: weighted tendency of qr for previous sub-timestep (Runge-Kutta)
     812    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ts_m       !< pointer: weighted tendency of s for previous sub-timestep (Runge-Kutta)
     813    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tsa_m      !< pointer: weighted tendency of sa for previous sub-timestep (Runge-Kutta)
     814    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tu_m       !< pointer: weighted tendency of u for previous sub-timestep (Runge-Kutta)
     815    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tv_m       !< pointer: weighted tendency of v for previous sub-timestep (Runge-Kutta)
     816    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tw_m       !< pointer: weighted tendency of w for previous sub-timestep (Runge-Kutta)
     817    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  u          !< pointer: horizontal velocity component u (x-direction)
     818    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  u_p        !< pointer: prognostic value of u
     819    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  v          !< pointer: horizontal velocity component v (y-direction)
     820    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  v_p        !< pointer: prognostic value of v
     821    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  vpt        !< pointer: virtual potential temperature
     822    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  w          !< pointer: vertical velocity component w (z-direction)
     823    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  w_p        !< pointer: prognostic value of w
    820824#endif
    821825
     
    971975    CHARACTER (LEN=1)    ::  cycle_mg = 'w'                               !< namelist parameter (see documentation)
    972976    CHARACTER (LEN=1)    ::  timestep_reason = ' '                        !< 'A'dvection or 'D'iffusion criterion, written to RUN_CONTROL file
    973     CHARACTER (LEN=3)    ::  coupling_char = ''                           !< appended to filenames in coupled ocean-atmosphere runs ('_O': ocean PE, '_A': atmosphere PE)
     977    CHARACTER (LEN=8)    ::  coupling_char = ''                           !< appended to filenames in coupled or nested runs ('_O': ocean PE,
     978                                                                          !< '_NV': vertically nested atmosphere PE, '_N##': PE of nested domain ##
    974979    CHARACTER (LEN=8)    ::  most_method = 'newton'                       !< namelist parameter
    975980    CHARACTER (LEN=8)    ::  run_date                                     !< date of simulation run, printed to HEADER file
  • palm/trunk/SOURCE/plant_canopy_model_mod.f90

    r2512 r2669  
    2525! -----------------
    2626! $Id$
     27! coupling_char removed
     28!
     29! 2512 2017-10-04 08:26:59Z raasch
    2730! upper bounds of 3d output changed from nx+1,ny+1 to nx,ny
    2831! no output of ghost layer data
     
    564567
    565568       USE control_parameters,                                                 &
    566            ONLY:  coupling_char, dz, humidity, io_blocks, io_group,            &
    567                   message_string, ocean, passive_scalar, urban_surface
     569           ONLY: dz, humidity, io_blocks, io_group, message_string, ocean,     &
     570                 passive_scalar, urban_surface
    568571
    569572       USE surface_mod,                                                        &
  • palm/trunk/SOURCE/pmc_interface_mod.f90

    r2663 r2669  
    2626! -----------------
    2727! $Id$
     28! file extension for nested domains changed to "_N##",
     29! created flag file in order to enable combine_plot_fields to process nest data
     30!
     31! 2663 2017-12-04 17:40:50Z suehring
    2832! Bugfix, wrong coarse-grid index in init_tkefactor used.
    2933!
     
    561565    IF ( cpl_id >= 2 )  THEN
    562566       nest_domain = .TRUE.
    563        WRITE( coupling_char, '(A1,I2.2)') '_', cpl_id
     567       WRITE( coupling_char, '(A2,I2.2)') '_N', cpl_id
    564568    ENDIF
    565569
     
    591595    IMPLICIT NONE
    592596
     597    INTEGER(iwp) ::  ncpl   !<  number of nest domains
     598
    593599    CALL location_message( 'setup the nested model configuration', .FALSE. )
    594600!
     
    605611!-- (e.g., all children have to follow the end_time settings of the root master)
    606612    CALL pmci_check_setting_mismatches
     613!
     614!-- Set flag file for combine_plot_fields for precessing the nest output data
     615    OPEN( 90, FILE='3DNESTING', FORM='FORMATTED' )
     616    CALL pmc_get_model_info( ncpl = ncpl )
     617    WRITE( 90, '(I2)' )  ncpl
     618    CLOSE( 90 )
    607619
    608620    CALL location_message( 'finished', .TRUE. )
  • palm/trunk/SOURCE/synthetic_turbulence_generator_mod.f90

    r2576 r2669  
    2525! -----------------
    2626! $Id$
     27! unit number for file containing turbulence generator data changed to 90
     28! bugfix: preprocessor directives added for MPI specific code
     29!
     30! 2576 2017-10-24 13:49:46Z Giersch
    2731! Definition of a new function called stg_skip_var_list to skip module
    2832! parameters during reading restart data
     
    312316    IMPLICIT NONE
    313317
     318#if defined( __parallel )
    314319    INTEGER(KIND=MPI_ADDRESS_KIND) :: extent !< extent of new MPI type
    315320    INTEGER(KIND=MPI_ADDRESS_KIND) :: tob=0  !< dummy variable
     321#endif
    316322
    317323    INTEGER(iwp) :: j                        !> loop index
     
    362368               tu(nzb:nzt+1),  tv(nzb:nzt+1),  tw(nzb:nzt+1)   )
    363369
     370#if defined( __parallel )
    364371!
    365372!-- Define MPI type used in stg_generate_seed_yz to gather vertical splitted
     
    391398       displs(j) = 0 + (nzt_x-nzb_x+1) * (j-1)
    392399    ENDDO
     400#endif
    393401
    394402!
     
    408416!-- zw: lwy, lwz, tw, r31, r32, r33, d3
    409417!-- WARNING: zz is not used at the moment
    410     OPEN( 24, FILE='STG_PROFILES'//TRIM( coupling_char ), STATUS='OLD',        &
     418    OPEN( 90, FILE='STG_PROFILES'//TRIM( coupling_char ), STATUS='OLD',        &
    411419                   FORM='FORMATTED')
    412420
    413421    ! Skip header
    414     READ( 24, * )
     422    READ( 90, * )
    415423
    416424    DO  k = nzb, nzt+1
    417        READ( 24, * ) zz, luy, luz, tu(k), lvy, lvz, tv(k), lwy, lwz, tw(k),    &
     425       READ( 90, * ) zz, luy, luz, tu(k), lvy, lvz, tv(k), lwy, lwz, tw(k),    &
    418426                     r11(k), r21(k), r22(k), r31(k), r32(k), r33(k),           &
    419427                     d1, d2, d3, d5
     
    438446    ENDDO
    439447
    440     CLOSE(24)
     448    CLOSE( 90 )
    441449
    442450!
  • palm/trunk/SOURCE/wind_turbine_model_mod.f90

    r2576 r2669  
    2626! -----------------
    2727! $Id$
     28! filename of turbine output changed to WTM_OUTPUT_DATA. File extension now
     29! includes the nest domain number. Turbine extension changed to "_T##"
     30!
     31! 2576 2017-10-24 13:49:46Z Giersch
    2832! Definition of a new function called wtm_skip_var_list to skip module
    2933! parameters during reading restart data
     
    113117
    114118    USE control_parameters,                                                    &
    115         ONLY:  dt_3d, dz, message_string, simulated_time, wind_turbine,        &
    116                initializing_actions
     119        ONLY:  coupling_char, dt_3d, dz, message_string, simulated_time,       &
     120               wind_turbine, initializing_actions
    117121
    118122    USE cpulog,                                                                &
     
    15561560       IMPLICIT NONE
    15571561
    1558        CHARACTER (LEN=2) ::  turbine_id
     1562       CHARACTER (LEN=4) ::  turbine_id
    15591563
    15601564       INTEGER(iwp) ::  i, j, k          !< loop indices
     
    23672371                ELSE
    23682372
    2369                    WRITE ( turbine_id,'(I2.2)')  inot
    2370                    OPEN ( 400+inot, FILE=( 'TURBINE_PARAMETERS'//turbine_id ), &
    2371                                             FORM='FORMATTED' )
     2373                   WRITE ( turbine_id,'(A2,I2.2)')  '_T', inot
     2374                   OPEN ( 400+inot, FILE=( 'WTM_OUTPUT_DATA' //                &
     2375                                           TRIM( coupling_char ) //            &
     2376                                           turbine_id ), FORM='FORMATTED' )
    23722377                   WRITE ( 400+inot, 105 ) inot
    23732378                   WRITE ( 400+inot, 106 ) simulated_time, omega_rot(inot),    &
Note: See TracChangeset for help on using the changeset viewer.