Ignore:
Timestamp:
Oct 26, 2016 4:53:23 PM (7 years ago)
Author:
gronemeier
Message:

Increased the number of possible statistic regions to 99

File:
1 edited

Legend:

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

    r2001 r2039  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Removed open of file 'PLOTTS_DATA' ( CASE(50:59) ) as it is no longer needed
    2323!
    2424! Former revisions:
     
    163163        ONLY:  cross_ts_numbers, cross_ts_number_count
    164164
    165     USE statistics,                                                            &
    166         ONLY:  region, statistic_regions
    167 
    168165
    169166    IMPLICIT NONE
     
    524521          ENDIF
    525522
    526        CASE ( 50:59 )
    527 
    528           IF ( statistic_regions == 0  .AND.  file_id == 50 )  THEN
    529              suffix = ''
    530           ELSE
    531              WRITE ( suffix, '(''_'',I1)' )  file_id - 50
    532           ENDIF
    533           OPEN ( file_id, FILE='PLOTTS_DATA'//TRIM( coupling_char )//          &
    534                                TRIM( suffix ),                                 &
    535                           FORM='FORMATTED', RECL=496 )
    536 !
    537 !--       Write PROFIL parameter file for output of time series
    538 !--       NOTE: To be on the safe side, this output is done at the beginning of
    539 !--             the model run (in case of collapse) and it is repeated in
    540 !--             close_file, then, however, with value ranges for the coordinate
    541 !--             systems
    542 !
    543 !--       Firstly determine the number of the coordinate systems to be drawn
    544           cranz = 0
    545           DO  j = 1, 10
    546              IF ( cross_ts_number_count(j) /= 0 )  cranz = cranz+1
    547           ENDDO
    548           rtext = '\1.0 ' // TRIM( run_description_header ) // '    ' //       &
    549                   TRIM( region( file_id - 50 ) )
    550 !
    551 !--       Write RAHMEN parameter
    552           OPEN ( 90, FILE='PLOTTS_PAR'//TRIM( coupling_char )//                &
    553                            TRIM( suffix ),                                     &
    554                      FORM='FORMATTED', DELIM='APOSTROPHE' )
    555           WRITE ( 90, RAHMEN )
    556 !
    557 !--       Determine and write CROSS parameters for the individual coordinate
    558 !--       systems
    559           DO  j = 1, 10
    560              k = cross_ts_number_count(j)
    561              IF ( k /= 0 )  THEN
    562 !
    563 !--             Store curve numbers, colours and line style
    564                 klist(1:k) = cross_ts_numbers(1:k,j)
    565                 klist(k+1:10) = 999999
    566 !
    567 !--             Write CROSS parameter
    568                 WRITE ( 90, CROSS )
    569 
    570              ENDIF
    571           ENDDO
    572 
    573           CLOSE ( 90 )
    574 !
    575 !--       Write all labels at the top of the data file, but only during the
    576 !--       first run of a sequence of jobs. The following jobs copy the time
    577 !--       series data to the bottom of that file.
    578           IF ( runnr == 0 )  THEN
    579              WRITE ( file_id, 5000 )  TRIM( run_description_header ) //        &
    580                                       '    ' // TRIM( region( file_id - 50 ) )
    581           ENDIF
    582 
    583 
    584523       CASE ( 80 )
    585524
Note: See TracChangeset for help on using the changeset viewer.