Changeset 2039 for palm/trunk/SOURCE


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

Increased the number of possible statistic regions to 99

Location:
palm/trunk/SOURCE
Files:
3 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
  • palm/trunk/SOURCE/check_parameters.f90

    r2038 r2039  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Removed check for statistic_regions > 9.
    2323!
    2424! Former revisions:
     
    19851985
    19861986!
    1987 !-- Check number of chosen statistic regions. More than 10 regions are not
    1988 !-- allowed, because so far no more than 10 corresponding output files can
    1989 !-- be opened (cf. check_open)
    1990     IF ( statistic_regions > 9  .OR.  statistic_regions < 0 )  THEN
     1987!-- Check number of chosen statistic regions
     1988    IF ( statistic_regions < 0 )  THEN
    19911989       WRITE ( message_string, * ) 'number of statistic_regions = ',           &
    1992                    statistic_regions+1, ' but only 10 regions are allowed'
     1990                   statistic_regions+1, ' is not allowed'
    19931991       CALL message( 'check_parameters', 'PA0082', 1, 2, 0, 6, 0 )
    19941992    ENDIF
  • palm/trunk/SOURCE/netcdf_interface_mod.f90

    r2038 r2039  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Increased number of possible statistic_regions to 99
    2323!
    2424! Former revisions:
     
    341341    INTEGER(iwp), DIMENSION(dopts_num,0:10) ::  id_var_dopts
    342342    INTEGER(iwp), DIMENSION(0:1,500)        ::  id_var_do2d, id_var_do3d
    343     INTEGER(iwp), DIMENSION(100,0:9)        ::  id_dim_z_pr, id_var_dopr, &
     343    INTEGER(iwp), DIMENSION(100,0:99)       ::  id_dim_z_pr, id_var_dopr, &
    344344                                                id_var_z_pr
    345     INTEGER(iwp), DIMENSION(dots_max,0:9)   ::  id_var_dots
     345    INTEGER(iwp), DIMENSION(dots_max,0:99)  ::  id_var_dots
    346346
    347347!
     
    469469    IMPLICIT NONE
    470470
    471     CHARACTER (LEN=2)              ::  suffix                !<
     471    CHARACTER (LEN=3)              ::  suffix                !<
    472472    CHARACTER (LEN=2), INTENT (IN) ::  callmode              !<
    473     CHARACTER (LEN=3)              ::  suffix1               !<
    474473    CHARACTER (LEN=4)              ::  grid_x                !<
    475474    CHARACTER (LEN=4)              ::  grid_y                !<
     
    39553954!--             names
    39563955                DO  j = 0, statistic_regions
    3957                    WRITE ( suffix, '(''_'',I1)' )  j
     3956                   WRITE ( suffix, '(''_'',I2.2)' )  j
    39583957
    39593958!
     
    40424041             ELSE
    40434042                DO  j = 0, statistic_regions
    4044                    WRITE ( suffix, '(''_'',I1)' )  j
     4043                   WRITE ( suffix, '(''_'',I2.2)' )  j
    40454044                   var_list = TRIM( var_list ) // TRIM( data_output_pr(i) ) // &
    40464045                              suffix // ';'
     
    41104109             ELSE
    41114110                DO  j = 0, statistic_regions
    4112                    WRITE ( suffix, '(''_'',I1)' )  j
     4111                   WRITE ( suffix, '(''_'',I2.2)' )  j
    41134112                   netcdf_var_name = TRIM( data_output_pr(i) ) // suffix
    41144113                   nc_stat = NF90_INQ_VARID( id_set_pr, netcdf_var_name, &
     
    41924191!--             names
    41934192                DO  j = 0, statistic_regions
    4194                    WRITE ( suffix, '(''_'',I1)' )  j
     4193                   WRITE ( suffix, '(''_'',I2.2)' )  j
    41954194
    41964195                   CALL netcdf_create_var( id_set_ts, (/ id_dim_time_ts /),    &
     
    42414240             ELSE
    42424241                DO  j = 0, statistic_regions
    4243                    WRITE ( suffix, '(''_'',I1)' )  j
     4242                   WRITE ( suffix, '(''_'',I2.2)' )  j
    42444243                   var_list = TRIM( var_list ) // TRIM( dots_label(i) ) // &
    42454244                              suffix // ';'
     
    43094308             ELSE
    43104309                DO  j = 0, statistic_regions
    4311                    WRITE ( suffix, '(''_'',I1)' )  j
     4310                   WRITE ( suffix, '(''_'',I2.2)' )  j
    43124311                   netcdf_var_name = TRIM( dots_label(i) ) // suffix
    43134312                   nc_stat = NF90_INQ_VARID( id_set_ts, netcdf_var_name, &
     
    48704869
    48714870                IF ( j == 0 )  THEN
    4872                    suffix1 = ''
     4871                   suffix = ''
    48734872                ELSE
    4874                    WRITE ( suffix1, '(''_'',I2.2)' )  j
     4873                   WRITE ( suffix, '(''_'',I2.2)' )  j
    48754874                ENDIF
    48764875
    48774876                IF ( j == 0 )  THEN
    48784877                   CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /),  &
    4879                                            TRIM( dopts_label(i) ) // suffix1,  &
     4878                                           TRIM( dopts_label(i) ) // suffix,  &
    48804879                                           nc_precision(6), id_var_dopts(i,j), &
    48814880                                           TRIM( dopts_unit(i) ),              &
     
    48844883                ELSE
    48854884                   CALL netcdf_create_var( id_set_pts, (/ id_dim_time_pts /),  &
    4886                                            TRIM( dopts_label(i) ) // suffix1,  &
     4885                                           TRIM( dopts_label(i) ) // suffix,  &
    48874886                                           nc_precision(6), id_var_dopts(i,j), &
    48884887                                           TRIM( dopts_unit(i) ),              &
    48894888                                           TRIM( dopts_label(i) ) // ' PG ' // &
    4890                                            suffix1(2:3), 400, 401, 402 )
     4889                                           suffix(2:3), 400, 401, 402 )
    48914890                ENDIF
    48924891
    48934892                var_list = TRIM( var_list ) // TRIM( dopts_label(i) ) // &
    4894                            suffix1 // ';'
     4893                           suffix // ';'
    48954894
    48964895                IF ( number_of_particle_groups == 1 )  EXIT
     
    49324931
    49334932                IF ( j == 0 )  THEN
    4934                    suffix1 = ''
     4933                   suffix = ''
    49354934                ELSE
    4936                    WRITE ( suffix1, '(''_'',I2.2)' )  j
     4935                   WRITE ( suffix, '(''_'',I2.2)' )  j
    49374936                ENDIF
    49384937
    49394938                var_list = TRIM( var_list ) // TRIM( dopts_label(i) ) // &
    4940                            suffix1 // ';'
     4939                           suffix // ';'
    49414940
    49424941                IF ( number_of_particle_groups == 1 )  EXIT
     
    50035002
    50045003                IF ( j == 0 )  THEN
    5005                    suffix1 = ''
     5004                   suffix = ''
    50065005                ELSE
    5007                    WRITE ( suffix1, '(''_'',I2.2)' )  j
     5006                   WRITE ( suffix, '(''_'',I2.2)' )  j
    50085007                ENDIF
    50095008
    5010                 netcdf_var_name = TRIM( dopts_label(i) ) // suffix1
     5009                netcdf_var_name = TRIM( dopts_label(i) ) // suffix
    50115010
    50125011                nc_stat = NF90_INQ_VARID( id_set_pts, netcdf_var_name, &
Note: See TracChangeset for help on using the changeset viewer.