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/data_output_profiles.f90

    r392 r964  
    44! Current revisions:
    55! -----------------
    6 !
     6! code for profil-output removed
    77!
    88! Former revisions:
     
    5252
    5353    INTEGER ::  i, id, ilc, ils, j, k, sr
    54     REAL    ::  uxma, uxmi
    55 
    5654
    5755!
     
    9189
    9290!
    93 !--    Open PROFIL-output files for each (sub-)region
    94        IF ( profil_output )  THEN
    95           DO  sr = 0, statistic_regions
    96              CALL check_open( 40 + sr )
    97           ENDDO
    98        ENDIF
    99 
    100 !
    10191!--    Increment the counter for number of output times
    10292       dopr_time_count = dopr_time_count + 1
    103 
    104 !
    105 !--    Re-set to zero the counter for the number of profiles already written
    106 !--    at the current output time into the respective crosses
    107        cross_pnc_local = 0
    10893
    10994!
     
    178163                   DO  sr = 0, statistic_regions
    179164
    180                       IF ( profil_output )  THEN
    181                          id = 40 + sr
    182 !
    183 !--                      Write Label-Header
    184                          WRITE ( id, 100 )  TRIM( data_output_pr(i) ), '(t=0)'
    185 !
    186 !--                      Write total profile
    187                          DO  k = nzb, nzt+1
    188                             WRITE ( id, 101 )  hom(k,2,dopr_initial_index(i),sr), &
    189                                                hom(k,1,dopr_initial_index(i),sr)
    190                          ENDDO
    191 !
    192 !--                      Write separation label
    193                          WRITE ( id, 102 )
    194                       ENDIF
    195 
    196165                      IF ( netcdf_output )  THEN
    197166#if defined( __netcdf )
     
    208177                   ENDDO
    209178
    210                    IF ( profil_output )  THEN
    211 !
    212 !--                   Determine indices for later NAMELIST-output (s. below)
    213                       profile_number = profile_number + 1
    214                       j = dopr_crossindex(i)
    215                       IF ( j /= 0 )  THEN
    216                          cross_profile_number_count(j) = &
    217                                                   cross_profile_number_count(j) + 1
    218                          k = cross_profile_number_count(j)
    219                          cross_profile_numbers(k,j) = profile_number
    220 !
    221 !--                      Initial profiles are always drawn as solid lines in
    222 !--                      anti-background colour.
    223                          cross_linecolors(k,j) = 1
    224                          cross_linestyles(k,j) = 0
    225 !
    226 !--                      If required, extend x-value range of the respective
    227 !--                      cross, provided it has not been specified in &
    228 !--                      check_parameters. Determination over all (sub-)regions.
    229                          IF ( cross_uxmin(j) == 0.0  .AND. &
    230                               cross_uxmax(j) == 0.0 )  THEN
    231 
    232                             DO  sr = 0, statistic_regions
    233 
    234                                uxmi = &
    235                                MINVAL( hom(:nz_do1d,1,dopr_initial_index(i),sr) )
    236  
    237                                uxma = &
    238                                MAXVAL( hom(:nz_do1d,1,dopr_initial_index(i),sr) )
    239 !
    240 !--                            When the value range of the first line in the
    241 !--                            corresponding cross is determined, its value range
    242 !--                            is simply adopted.
    243                                IF ( cross_uxmin_computed(j) > &
    244                                     cross_uxmax_computed(j) )  THEN
    245                                   cross_uxmin_computed(j) = uxmi
    246                                   cross_uxmax_computed(j) = uxma
    247                                ELSE
    248                                   cross_uxmin_computed(j) = &
    249                                                MIN( cross_uxmin_computed(j), uxmi )
    250                                   cross_uxmax_computed(j) = &
    251                                                MAX( cross_uxmax_computed(j), uxma )
    252                                ENDIF
    253 
    254                             ENDDO
    255 
    256                          ENDIF
    257 !
    258 !--                      If required, determine and note normalizing factors
    259                          SELECT CASE ( cross_normalized_x(j) )
    260    
    261                              CASE ( 'ts2' )
    262                                cross_normx_factor(k,j) = &
    263                                 ( hom_sum(nzb+3,pr_palm,normalizing_region) )**2
    264                             CASE ( 'wpt0' )
    265                                cross_normx_factor(k,j) = &
    266                                 hom_sum(nzb,18,normalizing_region)
    267                             CASE ( 'wsts2' )
    268                                cross_normx_factor(k,j) = &
    269                                 hom_sum(nzb+8,pr_palm,normalizing_region)  &
    270                               * ( hom_sum(nzb+3,pr_palm,normalizing_region) )**2
    271                             CASE ( 'ws2' )
    272                                cross_normx_factor(k,j) = &
    273                                 ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2
    274                             CASE ( 'ws2ts' )
    275                                cross_normx_factor(k,j) = &
    276                               ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2 &
    277                               * hom_sum(nzb+3,pr_palm,normalizing_region)
    278                              CASE ( 'ws3' )
    279                                cross_normx_factor(k,j) = &
    280                                 ( hom_sum(nzb+8,pr_palm,normalizing_region) )**3
    281 
    282                          END SELECT
    283 
    284                          SELECT CASE ( cross_normalized_y(j) )
    285  
    286                             CASE ( 'z_i' )
    287                                 cross_normy_factor(k,j) = &
    288                                         hom_sum(nzb+6,pr_palm,normalizing_region)
    289 
    290                          END SELECT
    291 
    292 !
    293 !--                      Check the normalizing factors for zeros and deactivate
    294 !--                      the normalization, if required.
    295                          IF ( cross_normx_factor(k,j) == 0.0  .OR. &
    296                               cross_normy_factor(k,j) == 0.0 )  THEN
    297                             WRITE( message_string, * ) 'data_output_profiles: ',  &
    298                                 'normalizing cross ',j, ' is not possible ',     &
    299                                 'since one of the & normalizing factors ',       &
    300                                  'is zero! & cross_normx_factor(',k,',',j,') = ', &
    301                                                          cross_normx_factor(k,j), &
    302                                  ' & cross_normy_factor(',k,',',j,') = ',         &
    303                                                          cross_normy_factor(k,j)
    304                             CALL message( 'data_output_profiles', 'PA0185',&
    305                                                                     0, 1, 0, 6, 0 )
    306                             cross_normx_factor(k,j) = 1.0
    307                             cross_normy_factor(k,j) = 1.0
    308                             cross_normalized_x(j) = ' '
    309                             cross_normalized_y(j) = ' '
    310                          ENDIF
    311 
    312 !
    313 !--                      If required, extend normalized x-value range of the
    314 !--                      respective cross, provided it has not been specified in
    315 !--                      check_parameters. Determination over all (sub-)regions.
    316                          IF ( cross_uxmin_normalized(j) == 0.0  .AND. &
    317                               cross_uxmax_normalized(j) == 0.0 )  THEN
    318 
    319                             DO  sr = 0, statistic_regions
    320 
    321                                uxmi = MINVAL( hom(:nz_do1d,1,             &
    322                                               dopr_initial_index(i),sr) ) / &
    323                                       cross_normx_factor(k,j)
    324                                uxma = MAXVAL( hom(:nz_do1d,1,             &
    325                                               dopr_initial_index(i),sr) ) / &
    326                                        cross_normx_factor(k,j)
    327 !
    328 !--                            When the value range of the first line in the
    329 !--                            corresponding cross is determined, its value range
    330 !--                            is simply adopted.
    331                                IF ( cross_uxmin_normalized_computed(j) > &
    332                                     cross_uxmax_normalized_computed(j) )  THEN
    333                                   cross_uxmin_normalized_computed(j) = uxmi
    334                                   cross_uxmax_normalized_computed(j) = uxma
    335                                ELSE
    336                                   cross_uxmin_normalized_computed(j) = &
    337                                     MIN( cross_uxmin_normalized_computed(j), uxmi )
    338                                   cross_uxmax_normalized_computed(j) = &
    339                                     MAX( cross_uxmax_normalized_computed(j), uxma )
    340                                ENDIF
    341 
    342                             ENDDO
    343 
    344                          ENDIF
    345 
    346                       ENDIF   ! Index determination
    347 
    348                    ENDIF   ! profil output
    349 
    350179                ENDIF   ! Initial profile available
    351180
     
    425254!--       Output for the individual (sub-)domains
    426255          DO  sr = 0, statistic_regions
    427 
    428              IF ( profil_output )  THEN
    429                 id = 40 + sr
    430 !
    431 !--             Write Label-Header
    432                 WRITE ( id, 100 )  TRIM( dopr_label(i) ), simulated_time_chr
    433 !
    434 !--             Output of total profile
    435                 DO  k = nzb, nzt+1
    436                    WRITE ( id, 101 )  hom(k,2,dopr_index(i),sr), &
    437                                       hom_sum(k,dopr_index(i),sr)
    438                 ENDDO
    439 !
    440 !--             Write separation label
    441                 WRITE ( id, 102 )
    442              ENDIF
    443256
    444257             IF ( netcdf_output )  THEN
     
    456269          ENDDO
    457270
    458           IF ( profil_output )  THEN
    459 !
    460 !--          Determine profile number on file and note the data for later
    461 !--          NAMELIST output, if the respective profile is to be drawn by
    462 !--          PROFIL (if it shall not be drawn, the variable dopr_crossindex has
    463 !--          the value 0, otherwise the number of the coordinate cross)
    464              profile_number = profile_number + 1
    465              j = dopr_crossindex(i)
    466 
    467              IF ( j /= 0 )  THEN
    468                 cross_profile_number_count(j) = cross_profile_number_count(j) +1
    469                 k = cross_profile_number_count(j)
    470                 cross_pnc_local(j)            = cross_pnc_local(j)            +1
    471                 cross_profile_numbers(k,j) = profile_number
    472                 ilc = MOD( dopr_time_count, 10 )
    473                 IF ( ilc == 0 )  ilc = 10
    474                 cross_linecolors(k,j) = linecolors(ilc)
    475                 ils = MOD( cross_pnc_local(j), 11 )
    476                 IF ( ils == 0 )  ils = 11
    477                 cross_linestyles(k,j) = linestyles(ils)
    478 !
    479 !--             If required, extend x-value range of the respective coordinate
    480 !--             cross, provided it has not been specified in check_parameters.
    481 !--             Determination over all (sub-)regions.
    482                 IF ( cross_uxmin(j) == 0.0  .AND.  cross_uxmax(j) == 0.0 )  THEN
    483 
    484                    DO  sr = 0, statistic_regions
    485 
    486                       uxmi = MINVAL( hom_sum(:nz_do1d,dopr_index(i),sr) )
    487                       uxma = MAXVAL( hom_sum(:nz_do1d,dopr_index(i),sr) )
    488 !
    489 !--                   When the value range of the first line in the
    490 !--                   corresponding cross is determined, its value range is
    491 !--                   simply adopted.
    492                       IF ( cross_uxmin_computed(j) > cross_uxmax_computed(j) ) &
    493                       THEN
    494                          cross_uxmin_computed(j) = uxmi
    495                          cross_uxmax_computed(j) = uxma
    496                       ELSE
    497                          cross_uxmin_computed(j) = &
    498                                            MIN( cross_uxmin_computed(j), uxmi )
    499                          cross_uxmax_computed(j) = &
    500                                            MAX( cross_uxmax_computed(j), uxma )
    501                       ENDIF
    502 
    503                    ENDDO
    504 
    505                 ENDIF
    506 !
    507 !--             If required, store the normalizing factors
    508                 SELECT CASE ( cross_normalized_x(j) )
    509 
    510                    CASE ( 'tsw2' )
    511                       cross_normx_factor(k,j) = &
    512                             ( hom_sum(nzb+11,pr_palm,normalizing_region) )**2
    513                    CASE ( 'wpt0' )
    514                       cross_normx_factor(k,j) = &
    515                               hom_sum(nzb,18,normalizing_region)
    516                    CASE ( 'wstsw2' )
    517                       cross_normx_factor(k,j) = &
    518                               hom_sum(nzb+8,pr_palm,normalizing_region)  &
    519                           * ( hom_sum(nzb+11,pr_palm,normalizing_region) )**2
    520                    CASE ( 'ws2' )
    521                       cross_normx_factor(k,j) = &
    522                             ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2
    523                    CASE ( 'ws2tsw' )
    524                       cross_normx_factor(k,j) = &
    525                             ( hom_sum(nzb+8,pr_palm,normalizing_region) )**2&
    526                             * hom_sum(nzb+11,pr_palm,normalizing_region)
    527                    CASE ( 'ws3' )
    528                       cross_normx_factor(k,j) = &
    529                             ( hom_sum(nzb+8,pr_palm,normalizing_region) )**3
    530 
    531                 END SELECT
    532                 SELECT CASE ( cross_normalized_y(j) )
    533 
    534                    CASE ( 'z_i' )
    535                       cross_normy_factor(k,j) = &
    536                                    hom_sum(nzb+6,pr_palm,normalizing_region)
    537 
    538                 END SELECT
    539 
    540 !
    541 !--             Check the normalizing factors for zeros and deactivate
    542 !--             the normalization, if required.
    543                 IF ( cross_normx_factor(k,j) == 0.0  .OR. &
    544                      cross_normy_factor(k,j) == 0.0 )  THEN
    545                    WRITE( message_string, * ) 'data_output_profiles: ',  &
    546                               'normalizing cross ',j, ' is not possible ',     &
    547                               'since one of the & normalizing factors ',       &
    548                               'is zero! & cross_normx_factor(',k,',',j,') = ', &
    549                                                       cross_normx_factor(k,j), &
    550                               ' & cross_normy_factor(',k,',',j,') = ',         &
    551                                                       cross_normy_factor(k,j)
    552                          CALL message( 'data_output_profiles', 'PA0185',&
    553                                                                 0, 1, 0, 6, 0 )
    554                     cross_normx_factor(k,j) = 1.0
    555                     cross_normy_factor(k,j) = 1.0
    556                     cross_normalized_x(j) = ' '
    557                     cross_normalized_y(j) = ' '
    558                 ENDIF
    559 
    560 !
    561 !--             If required, extend normalized x-value range of the respective 
    562 !--             cross, provided it has not been specified in check_parameters.
    563 !--             Determination over all (sub-)regions.
    564                 IF ( cross_uxmin_normalized(j) == 0.0  .AND. &
    565                      cross_uxmax_normalized(j) == 0.0 )  THEN
    566 
    567                    DO  sr = 0, statistic_regions
    568 
    569                       uxmi = MINVAL( hom(:nz_do1d,1,dopr_index(i),sr) ) / &
    570                              cross_normx_factor(k,j)
    571                       uxma = MAXVAL( hom(:nz_do1d,1,dopr_index(i),sr) ) / &
    572                              cross_normx_factor(k,j)
    573 !
    574 !--                   When the value range of the first line in the
    575 !--                   corresponding cross is determined, its value range is
    576 !--                   simply adopted.
    577                       IF ( cross_uxmin_normalized_computed(j) > &
    578                            cross_uxmax_normalized_computed(j) )  THEN
    579                          cross_uxmin_normalized_computed(j) = uxmi
    580                          cross_uxmax_normalized_computed(j) = uxma
    581                       ELSE
    582                          cross_uxmin_normalized_computed(j) = &
    583                                 MIN( cross_uxmin_normalized_computed(j), uxmi )
    584                          cross_uxmax_normalized_computed(j) = &
    585                                 MAX( cross_uxmax_normalized_computed(j), uxma )
    586                       ENDIF
    587 
    588                    ENDDO
    589 
    590                 ENDIF
    591 
    592              ENDIF   ! Index determination
    593 
    594           ENDIF   ! profil output
    595 
    596        ENDDO   ! Loop over dopr_n
     271       ENDDO
    597272
    598273    ENDIF  ! Output on PE0
Note: See TracChangeset for help on using the changeset viewer.