Ignore:
Timestamp:
Jul 26, 2012 9:14:24 AM (12 years ago)
Author:
raasch
Message:

old profil-parameters (cross_xtext, cross_normalized_x, etc. ) and respective code removed
(check_open, check_parameters, close_file, data_output_profiles, data_output_spectra, header, modules, parin)

reformatting (netcdf)

append feature removed from unit 14 (check_open)

File:
1 edited

Legend:

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

    r565 r964  
    44! Current revisions:
    55! -----------------
    6 !
     6! old profil-units (40:49) and respective code removed
    77!
    88! Former revisions:
     
    6767    CHARACTER (LEN=2)   ::  suffix
    6868    CHARACTER (LEN=10)  ::  datform = 'lit_endian'
    69     CHARACTER (LEN=80)  ::  rtext, title, utext = '', xtext = '', ytext = ''
    70 
    71     INTEGER ::  av, anzzeile, cranz, cross_count, cross_numbers, dimx, dimy, &
    72                 fid, file_id, j, k, legpos = 1, planz, timodex = 1
    73     INTEGER, DIMENSION(100) ::  klist, lstyle, cucol
    74 
    75     LOGICAL ::  checkuf = .TRUE., datleg = .TRUE., dp = .FALSE., &
    76                 grid = .TRUE., rand = .TRUE., swap, twoxa = .TRUE., &
    77                 twoya = .TRUE.
    78 
    79     REAL    ::  ansx = -999.999, ansy = -999.999, gwid = 0.1, rlegfak, &
    80                 sizex, sizey, texfac, utmove = 50.0, uxmax, uxmin, uymax, &
    81                 uymin, yright
    82     REAL, DIMENSION(100) ::  lwid, normx, normy
    83 
    84     NAMELIST /CROSS/   ansx, ansy, cucol, grid, gwid, klist, legpos, lstyle, &
    85                        lwid, normx, normy, rand, rlegfak, sizex, sizey, &
    86                        texfac, timodex, twoxa, twoya, utext, utmove, uxmax, &
    87                        uxmin, uymax, uymin, xtext, ytext
    88     NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dp, planz, sizex, sizey, &
    89                        title, yright
    90     NAMELIST /RAHMEN/  anzzeile, cranz, datleg, rtext, swap
     69    CHARACTER (LEN=80)  ::  rtext, title
     70
     71    INTEGER ::  av, anzzeile, dimx, dimy, &
     72                fid, file_id, j, k, planz
     73
     74    LOGICAL ::  checkuf = .TRUE., datleg = .TRUE., dp = .FALSE., swap
     75
     76    REAL ::  sizex, sizey, yright
     77
     78    NAMELIST /GLOBAL/  checkuf, datform, dimx, dimy, dp, planz, &
     79                       title
     80    NAMELIST /RAHMEN/  anzzeile, datleg, rtext, swap
    9181
    9282!
     
    190180                   WRITE ( 32, 3200)  ' ', TRIM( run_description_header ), &
    191181                                      nx+2, ny+2, nz_do3d+1, do3d_avs_n
    192                 ENDIF
    193 
    194              CASE ( 40:49 )
    195 !
    196 !--             Write PROFIL namelist parameters for 1D profiles.
    197 !--             First determine, how many crosses are to be drawn.
    198                 IF ( myid == 0 )  THEN
    199                    cross_numbers = 0
    200                    DO  j = 1, crmax
    201                       IF ( cross_profile_number_count(j) /= 0 )  THEN
    202                          cross_numbers = cross_numbers + 1
    203                       ENDIF
    204                    ENDDO
    205 
    206                    IF ( cross_numbers /= 0 )  THEN
    207 !
    208 !--                   Determine remaining RAHMEN parameters
    209                       swap = .FALSE.
    210                       rtext = '\0.5 ' // TRIM( run_description_header ) // &
    211                               '    ' // TRIM( region( fid - 40 ) )
    212 !
    213 !--                   Write RAHMEN parameters
    214                       IF ( statistic_regions == 0  .AND.  fid == 40 )  THEN
    215                          suffix = ''
    216                       ELSE
    217                          WRITE ( suffix, '(''_'',I1)' )  fid - 40
    218                       ENDIF
    219                       OPEN ( 90, FILE='PLOT1D_PAR' // TRIM( suffix ), &
    220                                  FORM='FORMATTED', DELIM='APOSTROPHE' )
    221 !
    222 !--                   Subtitle for crosses with time averaging
    223                       IF ( averaging_interval_pr /= 0.0 )  THEN
    224                          WRITE ( utext, 4000 )  averaging_interval_pr
    225                       ENDIF
    226 !
    227 !--                   Determine and write CROSS parameters for each individual
    228 !--                   cross
    229                       cross_count = 0
    230                       DO  j = 1, crmax
    231                          k = cross_profile_number_count(j)
    232                          IF ( k /= 0 )  THEN
    233                             cross_count = cross_count + 1
    234 !
    235 !--                         Write RAHMEN parameters
    236                             IF ( MOD( cross_count-1, &
    237                                       profile_rows*profile_columns ) == 0 ) &
    238                             THEN
    239 !
    240 !--                            Determine number of crosses still to be drawn
    241                                cranz = MIN( cross_numbers - cross_count + 1, &
    242                                             profile_rows * profile_columns )
    243 !
    244 !--                            If the first line cannot be filled with crosses
    245 !--                            completely, the default number of crosses per
    246 !--                            line has to be reduced.
    247                                IF ( cranz < profile_columns )  THEN
    248                                   anzzeile = cranz
    249                                ELSE
    250                                   anzzeile = profile_columns
    251                                ENDIF
    252 
    253                                WRITE ( 90, RAHMEN )
    254 
    255                             ENDIF
    256 !
    257 !--                         Store graph numbers
    258                             klist(1:k) = cross_profile_numbers(1:k,j)
    259                             klist(k+1:100) = 999999
    260 !
    261 !--                         Store graph attributes
    262                             cucol  = cross_linecolors(:,j)
    263                             lstyle = cross_linestyles(:,j)
    264                             lwid = 0.6
    265 !
    266 !--                         Sizes, text etc.
    267                             sizex = 100.0; sizey = 120.0
    268                             rlegfak = 0.7; texfac = 1.0
    269 !
    270 !--                         Determine range of x-axis values
    271                             IF ( cross_normalized_x(j) == ' ' )  THEN
    272 !
    273 !--                            Non-normalized profiles
    274                                IF ( cross_uxmin(j) == 0.0  .AND. &
    275                                     cross_uxmax(j) == 0.0 )  THEN
    276                                   uxmin = cross_uxmin_computed(j)
    277                                   uxmax = cross_uxmax_computed(j)
    278                                   IF ( uxmin == uxmax )  uxmax = uxmin + 1.0
    279                                ELSE
    280 !
    281 !--                               Values set in check_parameters are used here
    282                                   uxmin = cross_uxmin(j); uxmax = cross_uxmax(j)
    283                                ENDIF
    284                             ELSE
    285 !
    286 !--                            Normalized profiles
    287                                IF ( cross_uxmin_normalized(j) == 0.0  .AND. &
    288                                     cross_uxmax_normalized(j) == 0.0 )  THEN
    289                                   uxmin = cross_uxmin_normalized_computed(j)
    290                                   uxmax = cross_uxmax_normalized_computed(j)
    291                                   IF ( uxmin == uxmax )  uxmax = uxmin + 1.0
    292                                ELSE
    293 !
    294 !--                               Values set in check_parameters are used here
    295                                   uxmin = cross_uxmin_normalized(j)
    296                                   uxmax = cross_uxmax_normalized(j)
    297                                ENDIF
    298                             ENDIF
    299 !
    300 !--                         Range of y-axis values
    301 !--                         may be re-adjusted during normalization if required
    302                             uymin = cross_uymin(j); uymax = cross_uymax(j)
    303                             ytext = 'height in m'
    304 !
    305 !--                         Normalization of the axes
    306                             normx = cross_normx_factor(:,j)
    307                             normy = cross_normy_factor(:,j)
    308 !
    309 !--                         Labelling of the axes
    310                             IF ( cross_normalized_x(j) == ' ' )  THEN
    311                                xtext = cross_xtext(j)
    312                             ELSE
    313                                xtext = TRIM( cross_xtext(j) ) // ' / ' // &
    314                                        cross_normalized_x(j)
    315                             ENDIF
    316                             IF ( cross_normalized_y(j) == ' ' )  THEN
    317                                ytext = 'height in m'
    318                             ELSE
    319                                ytext = 'height in m' // ' / ' // &
    320                                        cross_normalized_y(j)
    321 !
    322 !--                            Determine upper limit of value range
    323                                IF ( z_max_do1d_normalized /= -1.0 )  THEN
    324                                   uymax = z_max_do1d_normalized
    325                                ENDIF
    326                             ENDIF
    327 
    328                             WRITE ( 90, CROSS )
    329 
    330                          ENDIF
    331                       ENDDO
    332 
    333                       CLOSE ( 90 )
    334                    ENDIF
    335                 ENDIF
    336 
    337              CASE ( 50:59 )
    338 !
    339 !--             Write PROFIL namelist parameters for time series
    340 !--             first determine number of crosses to be drawn
    341                 IF ( myid == 0 )  THEN
    342                    cranz = 0
    343                    DO  j = 1, 12
    344                       IF ( cross_ts_number_count(j) /= 0 )  cranz = cranz+1
    345                    ENDDO
    346 
    347                    IF ( cranz /= 0 )  THEN
    348 !
    349 !--                   Determine RAHMEN parameters
    350                       anzzeile = 1
    351                       swap = .TRUE.
    352                       rtext = '\1.0 ' // TRIM( run_description_header ) // &
    353                               '    ' // TRIM( region( fid - 50 ) )
    354 !
    355 !--                   Write RAHMEN parameters
    356                       IF ( statistic_regions == 0  .AND.  fid == 50 )  THEN
    357                          suffix = ''
    358                       ELSE
    359                          WRITE ( suffix, '(''_'',I1)' )  fid - 50
    360                       ENDIF
    361                       OPEN ( 90, FILE='PLOTTS_PAR' // TRIM( suffix ), &
    362                                  FORM='FORMATTED', DELIM='APOSTROPHE' )
    363                       WRITE ( 90, RAHMEN )
    364 !
    365 !--                   Determine and write CROSS parameters for each individual
    366 !--                   cross
    367                       DO  j = 1, 12
    368                          k = cross_ts_number_count(j)
    369                          IF ( k /= 0 )  THEN
    370 !
    371 !--                         Store graph numbers
    372                             klist(1:k) = cross_ts_numbers(1:k,j)
    373                             klist(k+1:100) = 999999
    374 !
    375 !--                         Store graph attributes
    376                             cucol(1:k)  = linecolors(1:k)
    377                             lstyle(1:k) = linestyles(1:k)
    378                             lwid = 0.4
    379 !
    380 !--                         Sizes, text etc.
    381                             sizex = 250.0; sizey = 40.0
    382                             rlegfak = 1.5; texfac = 1.5
    383                             xtext = 'time in s'
    384                             ytext = ''
    385                             utext = ''
    386 !
    387 !--                         Determine range of y-axis values
    388                             IF ( cross_ts_uymin(j) == 999.999 )  THEN
    389                                uymin = cross_ts_uymin_computed(j)
    390                             ELSE
    391                                uymin = cross_ts_uymin(j)
    392                             ENDIF
    393                             IF ( cross_ts_uymax(j) == 999.999 )  THEN
    394                                uymax = cross_ts_uymax_computed(j)
    395                             ELSE
    396                                uymax = cross_ts_uymax(j)
    397                             ENDIF
    398                             IF ( uymin == uymax )  uymax = uymin + 1.0
    399 !
    400 !--                         Range of x-axis values
    401                             uxmin = 0.0; uxmax = simulated_time
    402 !
    403 !--                         Normalizations
    404                             normx = 1.0; normy = 1.0
    405 
    406                             WRITE ( 90, CROSS )
    407 
    408                          ENDIF
    409                       ENDDO
    410 
    411                       CLOSE ( 90 )
    412                    ENDIF
    413182                ENDIF
    414183
Note: See TracChangeset for help on using the changeset viewer.