Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

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

    r1310 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    5258! 807 2012-01-25 11:53:51Z maronga
    5359! New cpp directive "__check" implemented which is used by check_namelist_files
    54 !
    55 ! Bugfix concerning opening of 3D files in restart runs in case of netCDF4
    56 !
    57 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    58 ! Output of total array size was adapted to nbgp.
    59 !
    60 ! 600 2010-11-24 16:10:51Z raasch
    61 ! bugfix in opening of cross section netcdf-files (parallel opening with
    62 ! netcdf4 only works for netcdf_data_format > 2)
    63 !
    64 ! 564 2010-09-30 13:18:59Z helmke
    65 ! start number of mask output files changed to 201, netcdf message identifiers
    66 ! of masked output changed
    67 !
    68 ! 519 2010-03-19 05:30:02Z raasch
    69 ! netCDF4 support for particle data
    70 !
    71 ! 493 2010-03-01 08:30:24Z raasch
    72 ! netCDF4 support (parallel output)
    73 !
    74 ! 410 2009-12-04 17:05:40Z letzel
    75 ! masked data output
    76 !
    77 ! 277 2009-03-31 09:13:47Z heinze
    78 ! Output of netCDF messages with aid of message handling routine.
    79 ! Output of messages replaced by message handling routine
    80 !
    81 ! 146 2008-01-17 13:08:34Z raasch
    82 ! First opening of unit 13 openes file _0000 on all PEs (parallel version)
    83 ! because only this file contains the global variables,
    84 ! myid_char_14 removed
    85 !
    86 ! 120 2007-10-17 11:54:43Z raasch
    87 ! Status of 3D-volume netCDF data file only depends on switch netcdf_64bit_3d
    88 !
    89 ! 105 2007-08-08 07:12:55Z raasch
    90 ! Different filenames are used in case of a coupled simulation,
    91 ! coupling_char added to all relevant filenames
    92 !
    93 ! 82 2007-04-16 15:40:52Z raasch
    94 ! Call of local_getenv removed, preprocessor directives for old systems removed
    95 !
    96 ! 46 2007-03-05 06:00:47Z raasch
    97 ! +netcdf_64bit_3d to switch on 64bit offset only for 3D files
    98 !
    99 ! RCS Log replace by Id keyword, revision history cleaned up
    100 !
    101 ! Revision 1.44  2006/08/22 13:48:34  raasch
    102 ! xz and yz cross sections now up to nzt+1
    10360!
    10461! Revision 1.1  1997/08/11 06:10:55  raasch
     
    11269!------------------------------------------------------------------------------!
    11370
    114     USE arrays_3d
    115     USE control_parameters
    116     USE grid_variables
    117     USE indices
     71    USE arrays_3d,                                                             &
     72        ONLY:  zu
     73
     74    USE control_parameters,                                                    &
     75        ONLY:  avs_data_file, avs_output, coupling_char,                       &
     76               data_output_2d_on_each_pe, do3d_compress, host, iso2d_output,   &
     77               message_string, mid, netcdf_data_format, nz_do3d, openfile,     &
     78               return_addres, return_username, run_description_header, runnr
     79
     80    USE grid_variables,                                                        &
     81        ONLY:  dx, dy
     82
     83    USE indices,                                                               &
     84        ONLY:  nbgp, nx, nxlg, nxrg, ny, nyng, nysg, nz, nzb
     85
     86    USE kinds
     87
    11888    USE netcdf_control
    119     USE particle_attributes
     89
     90    USE particle_attributes,                                                   &
     91        ONLY:  max_number_of_particle_groups, number_of_particle_groups,       &
     92               particle_groups
     93
    12094    USE pegrid
    121     USE precision_kind
    122     USE profil_parameter
    123     USE statistics
     95
     96    USE profil_parameter,                                                      &
     97        ONLY:  cross_ts_numbers, cross_ts_number_count
     98
     99    USE statistics,                                                            &
     100        ONLY:  region, statistic_regions
     101
    124102
    125103    IMPLICIT NONE
    126104
    127     CHARACTER (LEN=2)   ::  mask_char, suffix
    128     CHARACTER (LEN=20)  ::  xtext = 'time in s'
    129     CHARACTER (LEN=30)  ::  filename
    130     CHARACTER (LEN=40)  ::  avs_coor_file, avs_coor_file_localname, &
    131                             avs_data_file_localname
    132     CHARACTER (LEN=80)  ::  rtext
    133     CHARACTER (LEN=100) ::  avs_coor_file_catalog, avs_data_file_catalog, &
    134                             batch_scp, zeile
    135     CHARACTER (LEN=400) ::  command
    136 
    137     INTEGER ::  av, anzzeile = 1, cranz, file_id, i, iaddres, iusern, &
    138                 j, k, legpos = 1, timodex = 1
    139     INTEGER, DIMENSION(10) ::  klist
    140 
    141     LOGICAL ::  avs_coor_file_found = .FALSE., avs_data_file_found = .FALSE., &
    142                 datleg = .TRUE., get_filenames, grid = .TRUE., netcdf_extend, &
    143                 rand = .TRUE., swap = .TRUE., twoxa = .TRUE., twoya = .TRUE.
    144 
    145     REAL ::  ansx = -999.999, ansy = -999.999, gwid = 0.1, rlegfak = 1.5, &
    146              sizex = 250.0, sizey = 40.0, texfac = 1.5
    147 
    148     REAL, DIMENSION(:), ALLOCATABLE      ::  eta, ho, hu
    149     REAL(spk), DIMENSION(:), ALLOCATABLE ::  xkoor, ykoor, zkoor 
    150 
    151 
    152     NAMELIST /RAHMEN/  anzzeile, cranz, datleg, rtext, swap
    153     NAMELIST /CROSS/   ansx, ansy, grid, gwid, klist, legpos, &
    154                        rand, rlegfak, sizex, sizey, texfac, &
     105    CHARACTER (LEN=2)   ::  mask_char               !:
     106    CHARACTER (LEN=2)   ::  suffix                  !:
     107    CHARACTER (LEN=20)  ::  xtext = 'time in s'     !:
     108    CHARACTER (LEN=30)  ::  filename                !:
     109    CHARACTER (LEN=40)  ::  avs_coor_file           !:
     110    CHARACTER (LEN=40)  ::  avs_coor_file_localname !:
     111    CHARACTER (LEN=40)  ::  avs_data_file_localname !:
     112    CHARACTER (LEN=80)  ::  rtext                   !:
     113    CHARACTER (LEN=100) ::  avs_coor_file_catalog   !:
     114    CHARACTER (LEN=100) ::  avs_data_file_catalog   !:
     115    CHARACTER (LEN=100) ::  batch_scp               !:
     116    CHARACTER (LEN=100) ::  line                    !:
     117    CHARACTER (LEN=400) ::  command                 !:
     118
     119    INTEGER(iwp) ::  av          !:
     120    INTEGER(iwp) ::  numline = 1 !:
     121    INTEGER(iwp) ::  cranz       !:
     122    INTEGER(iwp) ::  file_id     !:
     123    INTEGER(iwp) ::  i           !:
     124    INTEGER(iwp) ::  iaddres     !:
     125    INTEGER(iwp) ::  iusern      !:
     126    INTEGER(iwp) ::  j           !:
     127    INTEGER(iwp) ::  k           !:
     128    INTEGER(iwp) ::  legpos = 1  !:
     129    INTEGER(iwp) ::  timodex = 1 !:
     130   
     131    INTEGER(iwp), DIMENSION(10) ::  klist !:
     132
     133    LOGICAL ::  avs_coor_file_found = .FALSE. !:
     134    LOGICAL ::  avs_data_file_found = .FALSE. !:
     135    LOGICAL ::  datleg = .TRUE.               !:
     136    LOGICAL ::  get_filenames                 !:
     137    LOGICAL ::  grid = .TRUE.                 !:
     138    LOGICAL ::  netcdf_extend                 !:
     139    LOGICAL ::  rand = .TRUE.                 !:
     140    LOGICAL ::  swap = .TRUE.                 !:
     141    LOGICAL ::  twoxa = .TRUE.                !:
     142    LOGICAL ::  twoya = .TRUE.                !:
     143
     144    REAL(wp) ::  ansx = -999.999 !:
     145    REAL(wp) ::  ansy = -999.999 !:
     146    REAL(wp) ::  gwid = 0.1      !:
     147    REAL(wp) ::  rlegfak = 1.5   !:
     148    REAL(wp) ::  sizex = 250.0   !:
     149    REAL(wp) ::  sizey = 40.0    !:
     150    REAL(wp) ::  texfac = 1.5    !:
     151
     152    REAL(wp), DIMENSION(:), ALLOCATABLE      ::  eta !:
     153    REAL(wp), DIMENSION(:), ALLOCATABLE      ::  ho  !:
     154    REAL(wp), DIMENSION(:), ALLOCATABLE      ::  hu  !:
     155   
     156    REAL(sp), DIMENSION(:), ALLOCATABLE ::  xkoor !:
     157    REAL(sp), DIMENSION(:), ALLOCATABLE ::  ykoor !:
     158    REAL(sp), DIMENSION(:), ALLOCATABLE ::  zkoor !: 
     159
     160
     161    NAMELIST /RAHMEN/  numline, cranz, datleg, rtext, swap
     162    NAMELIST /CROSS/   ansx, ansy, grid, gwid, klist, legpos,                  &
     163                       rand, rlegfak, sizex, sizey, texfac,                    &
    155164                       timodex, twoxa, twoya, xtext
    156165                       
     
    169178          CASE ( 13, 14, 21, 22, 23, 80:85 )
    170179             IF ( file_id == 14 .AND. openfile(file_id)%opened_before )  THEN
    171                 message_string = 're-open of unit ' // &
     180                message_string = 're-open of unit ' //                         &
    172181                                 '14 is not verified. Please check results!'
    173182                CALL message( 'check_open', 'PA0165', 0, 1, 0, 6, 0 )       
     
    175184
    176185          CASE DEFAULT
    177              WRITE( message_string, * ) 're-opening of file-id ', file_id, &
     186             WRITE( message_string, * ) 're-opening of file-id ', file_id,     &
    178187                                        ' is not allowed'
    179188             CALL message( 'check_open', 'PA0166', 0, 1, 0, 6, 0 )   
     
    192201             
    193202          IF ( myid /= 0 )  THEN
    194              WRITE( message_string, * ) 'opening file-id ',file_id, &
     203             WRITE( message_string, * ) 'opening file-id ',file_id,            &
    195204                                        ' not allowed for PE ',myid
    196205             CALL message( 'check_open', 'PA0167', 2, 2, -1, 6, 1 )
     
    202211         
    203212             IF ( myid /= 0 )  THEN
    204                 WRITE( message_string, * ) 'opening file-id ',file_id, &
     213                WRITE( message_string, * ) 'opening file-id ',file_id,         &
    205214                                           ' not allowed for PE ',myid
    206215                CALL message( 'check_open', 'PA0167', 2, 2, -1, 6, 1 )
     
    213222          IF ( .NOT.  data_output_2d_on_each_pe )  THEN
    214223             IF ( myid /= 0 )  THEN
    215                 WRITE( message_string, * ) 'opening file-id ',file_id, &
     224                WRITE( message_string, * ) 'opening file-id ',file_id,         &
    216225                                           ' not allowed for PE ',myid
    217226                CALL message( 'check_open', 'PA0167', 2, 2, -1, 6, 1 )
     
    223232!
    224233!--       File-ids that are used temporarily in other routines
    225           WRITE( message_string, * ) 'opening file-id ',file_id, &
     234          WRITE( message_string, * ) 'opening file-id ',file_id,               &
    226235                                    ' is not allowed since it is used otherwise'
    227236          CALL message( 'check_open', 'PA0168', 0, 1, 0, 6, 0 )
     
    241250!--       check_namelist_files!
    242251          IF ( check_restart == 2 ) THEN
    243              OPEN ( 11, FILE='PARINF'//coupling_char, FORM='FORMATTED', &
     252             OPEN ( 11, FILE='PARINF'//coupling_char, FORM='FORMATTED',        &
    244253                        STATUS='OLD' )
    245254          ELSE
    246              OPEN ( 11, FILE='PARIN'//coupling_char, FORM='FORMATTED', &
     255             OPEN ( 11, FILE='PARIN'//coupling_char, FORM='FORMATTED',         &
    247256                        STATUS='OLD' )
    248257          END IF
    249258#else
    250259
    251           OPEN ( 11, FILE='PARIN'//coupling_char, FORM='FORMATTED', &
     260          OPEN ( 11, FILE='PARIN'//coupling_char, FORM='FORMATTED',            &
    252261                     STATUS='OLD' )
    253262#endif
     
    256265
    257266          IF ( myid_char == '' )  THEN
    258              OPEN ( 13, FILE='BININ'//coupling_char//myid_char, &
     267             OPEN ( 13, FILE='BININ'//coupling_char//myid_char,                &
    259268                        FORM='UNFORMATTED', STATUS='OLD' )
    260269          ELSE
     
    263272!--          this file contains the global variables
    264273             IF ( .NOT. openfile(file_id)%opened_before )  THEN
    265                 OPEN ( 13, FILE='BININ'//TRIM( coupling_char )//'/_0000',&
     274                OPEN ( 13, FILE='BININ'//TRIM( coupling_char )//'/_0000',      &
    266275                           FORM='UNFORMATTED', STATUS='OLD' )
    267276             ELSE
     
    274283
    275284          IF ( myid_char == '' )  THEN
    276              OPEN ( 14, FILE='BINOUT'//coupling_char//myid_char, &
     285             OPEN ( 14, FILE='BINOUT'//coupling_char//myid_char,               &
    277286                        FORM='UNFORMATTED', POSITION='APPEND' )
    278287          ELSE
     
    286295             CALL MPI_BARRIER( comm2d, ierr )
    287296#endif
    288              OPEN ( 14, FILE='BINOUT'//TRIM(coupling_char)//'/'//myid_char, &
     297             OPEN ( 14, FILE='BINOUT'//TRIM(coupling_char)//'/'//myid_char,    &
    289298                        FORM='UNFORMATTED' )
    290299          ENDIF
     
    316325          ENDIF
    317326          IF ( myid_char == '' )  THEN
    318              OPEN ( 20, FILE='DATA_LOG'//TRIM( coupling_char )//'/_0000', &
     327             OPEN ( 20, FILE='DATA_LOG'//TRIM( coupling_char )//'/_0000',      &
    319328                        FORM='UNFORMATTED', POSITION='APPEND' )
    320329          ELSE
     
    332341
    333342          IF ( data_output_2d_on_each_pe )  THEN
    334              OPEN ( 21, FILE='PLOT2D_XY'//TRIM( coupling_char )//myid_char, &
     343             OPEN ( 21, FILE='PLOT2D_XY'//TRIM( coupling_char )//myid_char,    &
    335344                        FORM='UNFORMATTED', POSITION='APPEND' )
    336345          ELSE
    337              OPEN ( 21, FILE='PLOT2D_XY'//coupling_char, &
     346             OPEN ( 21, FILE='PLOT2D_XY'//coupling_char,                       &
    338347                        FORM='UNFORMATTED', POSITION='APPEND' )
    339348          ENDIF
     
    363372!--          Create output file for local parameters
    364373             IF ( iso2d_output )  THEN
    365                 OPEN ( 27, FILE='PLOT2D_XY_LOCAL'//coupling_char, &
     374                OPEN ( 27, FILE='PLOT2D_XY_LOCAL'//coupling_char,              &
    366375                           FORM='FORMATTED', DELIM='APOSTROPHE' )
    367376                openfile(27)%opened = .TRUE.
     
    373382
    374383          IF ( data_output_2d_on_each_pe )  THEN
    375              OPEN ( 22, FILE='PLOT2D_XZ'//TRIM( coupling_char )//myid_char, &
     384             OPEN ( 22, FILE='PLOT2D_XZ'//TRIM( coupling_char )//myid_char,    &
    376385                        FORM='UNFORMATTED', POSITION='APPEND' )
    377386          ELSE
    378              OPEN ( 22, FILE='PLOT2D_XZ'//coupling_char, FORM='UNFORMATTED', &
     387             OPEN ( 22, FILE='PLOT2D_XZ'//coupling_char, FORM='UNFORMATTED',   &
    379388                        POSITION='APPEND' )
    380389          ENDIF
     
    402411!
    403412!--          Create output file for local parameters
    404              OPEN ( 28, FILE='PLOT2D_XZ_LOCAL'//coupling_char, &
     413             OPEN ( 28, FILE='PLOT2D_XZ_LOCAL'//coupling_char,                 &
    405414                        FORM='FORMATTED', DELIM='APOSTROPHE' )
    406415             openfile(28)%opened = .TRUE.
     
    411420
    412421          IF ( data_output_2d_on_each_pe )  THEN
    413              OPEN ( 23, FILE='PLOT2D_YZ'//TRIM( coupling_char )//myid_char, &
     422             OPEN ( 23, FILE='PLOT2D_YZ'//TRIM( coupling_char )//myid_char,    &
    414423                        FORM='UNFORMATTED', POSITION='APPEND' )
    415424          ELSE
    416              OPEN ( 23, FILE='PLOT2D_YZ'//coupling_char, FORM='UNFORMATTED', &
     425             OPEN ( 23, FILE='PLOT2D_YZ'//coupling_char, FORM='UNFORMATTED',   &
    417426                        POSITION='APPEND' )
    418427          ENDIF
     
    440449!
    441450!--          Create output file for local parameters
    442              OPEN ( 29, FILE='PLOT2D_YZ_LOCAL'//coupling_char, &
     451             OPEN ( 29, FILE='PLOT2D_YZ_LOCAL'//coupling_char,                 &
    443452                        FORM='FORMATTED', DELIM='APOSTROPHE' )
    444453             openfile(29)%opened = .TRUE.
     
    448457       CASE ( 30 )
    449458
    450           OPEN ( 30, FILE='PLOT3D_DATA'//TRIM( coupling_char )//myid_char, &
     459          OPEN ( 30, FILE='PLOT3D_DATA'//TRIM( coupling_char )//myid_char,     &
    451460                     FORM='UNFORMATTED' )
    452461!
     
    471480
    472481                OPEN ( 3, FILE='OUTPUT_FILE_CONNECTIONS', FORM='FORMATTED' )
    473                 DO  WHILE ( .NOT. avs_coor_file_found  .OR. &
     482                DO  WHILE ( .NOT. avs_coor_file_found  .OR.                    &
    474483                            .NOT. avs_data_file_found )
    475484
    476                    READ ( 3, '(A)', END=1 )  zeile
    477 
    478                    SELECT CASE ( zeile(1:11) )
     485                   READ ( 3, '(A)', END=1 )  line
     486
     487                   SELECT CASE ( line(1:11) )
    479488
    480489                      CASE ( 'PLOT3D_COOR' )
    481                          READ ( 3, '(A/A)' )  avs_coor_file_catalog, &
     490                         READ ( 3, '(A/A)' )  avs_coor_file_catalog,           &
    482491                                              avs_coor_file_localname
    483492                         avs_coor_file_found = .TRUE.
    484493
    485494                      CASE ( 'PLOT3D_DATA' )
    486                          READ ( 3, '(A/A)' )  avs_data_file_catalog, &
     495                         READ ( 3, '(A/A)' )  avs_data_file_catalog,           &
    487496                                              avs_data_file_localname
    488497                         avs_data_file_found = .TRUE.
    489498
    490499                      CASE DEFAULT
    491                          READ ( 3, '(A/A)' )  zeile, zeile
     500                         READ ( 3, '(A/A)' )  line, line
    492501
    493502                   END SELECT
     
    498507!--             using batch_scp
    499508       1        CLOSE ( 3 )
    500                 IF ( .NOT. avs_coor_file_found  .OR. &
     509                IF ( .NOT. avs_coor_file_found  .OR.                           &
    501510                     .NOT. avs_data_file_found )  THEN
    502                    message_string= 'no filename for AVS-data-file ' //       &
    503                                    'found in MRUN-config-file' //            &
     511                   message_string= 'no filename for AVS-data-file ' //         &
     512                                   'found in MRUN-config-file' //              &
    504513                                   ' &filename in FLD-file set to "unknown"'
    505514                   CALL message( 'check_open', 'PA0169', 0, 1, 0, 6, 0 )
     
    509518                ELSE
    510519                   get_filenames = .TRUE.
    511                    IF ( TRIM( host ) == 'hpmuk'  .OR.  &
     520                   IF ( TRIM( host ) == 'hpmuk'  .OR.                          &
    512521                        TRIM( host ) == 'lcmuk' )  THEN
    513522                      batch_scp = '/home/raasch/pub/batch_scp'
    514523                   ELSEIF ( TRIM( host ) == 'nech' )  THEN
    515524                      batch_scp = '/ipf/b/b323011/pub/batch_scp'
    516                    ELSEIF ( TRIM( host ) == 'ibmh'  .OR.  &
     525                   ELSEIF ( TRIM( host ) == 'ibmh'  .OR.                       &
    517526                            TRIM( host ) == 'ibmb' )  THEN
    518527                      batch_scp = '/home/h/niksiraa/pub/batch_scp'
     
    520529                      batch_scp = '/home/nhbksira/pub/batch_scp'
    521530                   ELSE
    522                       message_string= 'no path for batch_scp on host "' // &
     531                      message_string= 'no path for batch_scp on host "' //     &
    523532                                       TRIM( host ) // '"'
    524533                      CALL message( 'check_open', 'PA0170', 0, 1, 0, 6, 0 )
     
    531540!--                   /etc/passwd serves as Dummy-Datei, because it is not
    532541!--                   really transferred.
    533                       command = TRIM( batch_scp ) // ' -n -u ' // &
    534                          return_username(1:iusern) // ' ' // &
    535                          return_addres(1:iaddres) // ' /etc/passwd "' // &
    536                          TRIM( avs_coor_file_catalog ) // '" ' // &
     542                      command = TRIM( batch_scp ) // ' -n -u ' //              &
     543                         return_username(1:iusern) // ' ' //                   &
     544                         return_addres(1:iaddres) // ' /etc/passwd "' //       &
     545                         TRIM( avs_coor_file_catalog ) // '" ' //              &
    537546                         TRIM( avs_coor_file_localname ) // ' > REMOTE_FILENAME'
    538547
     
    543552!
    544553!--                   Determine the data file name
    545                       command = TRIM( batch_scp ) // ' -n -u ' // &
    546                          return_username(1:iusern) // ' ' // &
    547                          return_addres(1:iaddres) // ' /etc/passwd "' // &
    548                          TRIM( avs_data_file_catalog ) // '" ' // &
     554                      command = TRIM( batch_scp ) // ' -n -u ' //              &
     555                         return_username(1:iusern) // ' ' //                   &
     556                         return_addres(1:iaddres) // ' /etc/passwd "' //       &
     557                         TRIM( avs_data_file_catalog ) // '" ' //              &
    549558                         TRIM( avs_data_file_localname ) // ' > REMOTE_FILENAME'
    550559
     
    567576                OPEN ( 33, FILE='PLOT3D_FLD_COOR', FORM='FORMATTED' )
    568577                openfile(33)%opened = .TRUE.
    569                 WRITE ( 33, 3300 )  TRIM( avs_coor_file ), &
    570                                     TRIM( avs_coor_file ), (nx+2*nbgp)*4, &
     578                WRITE ( 33, 3300 )  TRIM( avs_coor_file ),                     &
     579                                    TRIM( avs_coor_file ), (nx+2*nbgp)*4,      &
    571580                                    TRIM( avs_coor_file ), (nx+2*nbgp)*4+(ny+2*nbgp)*4
    572581           
     
    623632             WRITE ( suffix, '(''_'',I1)' )  file_id - 50
    624633          ENDIF
    625           OPEN ( file_id, FILE='PLOTTS_DATA'//TRIM( coupling_char )// &
    626                                TRIM( suffix ),                        &
     634          OPEN ( file_id, FILE='PLOTTS_DATA'//TRIM( coupling_char )//          &
     635                               TRIM( suffix ),                                 &
    627636                          FORM='FORMATTED', RECL=496 )
    628637!
     
    638647             IF ( cross_ts_number_count(j) /= 0 )  cranz = cranz+1
    639648          ENDDO
    640           rtext = '\1.0 ' // TRIM( run_description_header ) // '    ' // &
     649          rtext = '\1.0 ' // TRIM( run_description_header ) // '    ' //       &
    641650                  TRIM( region( file_id - 50 ) )
    642651!
    643652!--       Write RAHMEN parameter
    644           OPEN ( 90, FILE='PLOTTS_PAR'//TRIM( coupling_char )// &
    645                            TRIM( suffix ),                      &
     653          OPEN ( 90, FILE='PLOTTS_PAR'//TRIM( coupling_char )//                &
     654                           TRIM( suffix ),                                     &
    646655                     FORM='FORMATTED', DELIM='APOSTROPHE' )
    647656          WRITE ( 90, RAHMEN )
     
    669678!--       series data to the bottom of that file.
    670679          IF ( runnr == 0 )  THEN
    671              WRITE ( file_id, 5000 )  TRIM( run_description_header ) // &
     680             WRITE ( file_id, 5000 )  TRIM( run_description_header ) //        &
    672681                                      '    ' // TRIM( region( file_id - 50 ) )
    673682          ENDIF
     
    694703             ENDIF
    695704#endif
    696              OPEN ( 80, FILE='PARTICLE_INFOS'//TRIM( coupling_char )//'/'// &
    697                              myid_char,                                     &
     705             OPEN ( 80, FILE='PARTICLE_INFOS'//TRIM( coupling_char )//'/'//    &
     706                             myid_char,                                        &
    698707                        FORM='FORMATTED', POSITION='APPEND' )
    699708          ENDIF
     
    705714       CASE ( 81 )
    706715
    707              OPEN ( 81, FILE='PLOTSP_X_PAR'//coupling_char, FORM='FORMATTED', &
     716             OPEN ( 81, FILE='PLOTSP_X_PAR'//coupling_char, FORM='FORMATTED',  &
    708717                        DELIM='APOSTROPHE', RECL=1500, POSITION='APPEND' )
    709718
     
    715724       CASE ( 83 )
    716725
    717              OPEN ( 83, FILE='PLOTSP_Y_PAR'//coupling_char, FORM='FORMATTED', &
     726             OPEN ( 83, FILE='PLOTSP_Y_PAR'//coupling_char, FORM='FORMATTED',  &
    718727                        DELIM='APOSTROPHE', RECL=1500, POSITION='APPEND' )
    719728
     
    726735
    727736          IF ( myid_char == '' )  THEN
    728              OPEN ( 85, FILE='PARTICLE_DATA'//TRIM(coupling_char)//myid_char, &
     737             OPEN ( 85, FILE='PARTICLE_DATA'//TRIM(coupling_char)//myid_char,  &
    729738                        FORM='UNFORMATTED', POSITION='APPEND' )
    730739          ELSE
     
    738747             CALL MPI_BARRIER( comm2d, ierr )
    739748#endif
    740              OPEN ( 85, FILE='PARTICLE_DATA'//TRIM( coupling_char )//'/'// &
    741                         myid_char,                                         &
     749             OPEN ( 85, FILE='PARTICLE_DATA'//TRIM( coupling_char )//'/'//     &
     750                        myid_char,                                             &
    742751                        FORM='UNFORMATTED', POSITION='APPEND' )
    743752          ENDIF
     
    751760             rtext = 'data format version 3.0'
    752761             WRITE ( 85 )  rtext
    753              WRITE ( 85 )  number_of_particle_groups, &
     762             WRITE ( 85 )  number_of_particle_groups,                          &
    754763                           max_number_of_particle_groups
    755764             WRITE ( 85 )  particle_groups
     
    11101119             filename = 'DATA_PRT_NETCDF' // coupling_char
    11111120          ELSE
    1112              filename = 'DATA_PRT_NETCDF' // TRIM( coupling_char ) // '/' // &
     1121             filename = 'DATA_PRT_NETCDF' // TRIM( coupling_char ) // '/' //   &
    11131122                        myid_char
    11141123          ENDIF
     
    11431152!--          For runs on multiple processors create the subdirectory
    11441153             IF ( myid_char /= '' )  THEN
    1145                 IF ( myid == 0  .AND. .NOT. openfile(file_id)%opened_before ) &
     1154                IF ( myid == 0  .AND. .NOT. openfile(file_id)%opened_before )  &
    11461155                THEN    ! needs modification in case of non-extendable sets
    1147                    CALL local_system( 'mkdir  DATA_PRT_NETCDF' // &
     1156                   CALL local_system( 'mkdir  DATA_PRT_NETCDF' //              &
    11481157                                       TRIM( coupling_char ) // '/' )
    11491158                ENDIF
     
    12171226             mid = file_id - (200+max_masks)
    12181227             WRITE ( mask_char,'(I2.2)')  mid
    1219              filename = 'DATA_MASK_' // mask_char // '_AV_NETCDF' // &
     1228             filename = 'DATA_MASK_' // mask_char // '_AV_NETCDF' //           &
    12201229                  coupling_char
    12211230             av = 1
     
    12301239!
    12311240!--          Open an existing netCDF file for output
    1232              CALL open_write_netcdf_file( filename, id_set_mask(mid,av), &
     1241             CALL open_write_netcdf_file( filename, id_set_mask(mid,av),       &
    12331242                                          .TRUE., 456 )
    12341243!
     
    12821291!
    12831292!-- Formats
    1284 3300 FORMAT ('#'/                                                   &
    1285              'coord 1  file=',A,'  filetype=unformatted'/           &
    1286              'coord 2  file=',A,'  filetype=unformatted  skip=',I6/ &
    1287              'coord 3  file=',A,'  filetype=unformatted  skip=',I6/ &
     12933300 FORMAT ('#'/                                                              &
     1294             'coord 1  file=',A,'  filetype=unformatted'/                      &
     1295             'coord 2  file=',A,'  filetype=unformatted  skip=',I6/            &
     1296             'coord 3  file=',A,'  filetype=unformatted  skip=',I6/            &
    12881297             '#')
    128912984000 FORMAT ('# ',A)
    1290 5000 FORMAT ('# ',A/                                                          &
    1291              '#1 E'/'#2 E*'/'#3 dt'/'#4 u*'/'#5 th*'/'#6 umax'/'#7 vmax'/     &
    1292              '#8 wmax'/'#9 div_new'/'#10 div_old'/'#11 z_i_wpt'/'#12 z_i_pt'/ &
    1293              '#13 w*'/'#14 w''pt''0'/'#15 w''pt'''/'#16 wpt'/'#17 pt(0)'/     &
     12995000 FORMAT ('# ',A/                                                           &
     1300             '#1 E'/'#2 E*'/'#3 dt'/'#4 u*'/'#5 th*'/'#6 umax'/'#7 vmax'/      &
     1301             '#8 wmax'/'#9 div_new'/'#10 div_old'/'#11 z_i_wpt'/'#12 z_i_pt'/  &
     1302             '#13 w*'/'#14 w''pt''0'/'#15 w''pt'''/'#16 wpt'/'#17 pt(0)'/      &
    12941303             '#18 pt(zp)'/'#19 splptx'/'#20 splpty'/'#21 splptz')
    1295 8000 FORMAT (A/                                                            &
    1296              '  step    time  # of parts   lPE sent/recv  rPE sent/recv  ',&
    1297              'sPE sent/recv  nPE sent/recv  max # of parts'/               &
     13048000 FORMAT (A/                                                                &
     1305             '  step    time  # of parts   lPE sent/recv  rPE sent/recv  ',    &
     1306             'sPE sent/recv  nPE sent/recv  max # of parts'/                   &
    12981307             103('-'))
    12991308
Note: See TracChangeset for help on using the changeset viewer.