Ignore:
Timestamp:
Jun 25, 2020 9:53:58 AM (4 years ago)
Author:
raasch
Message:

further re-formatting to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4360 r4577  
    11!> @file data_output_profiles.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
    9 !
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
    13 !
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
     8!
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
     12!
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
     
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4360 2020-01-07 11:25:50Z suehring
    2729! Corrected "Former revisions" section
    28 ! 
     30!
    2931! 3655 2019-01-07 16:51:22Z knoop
    3032! add variable description
     
    3739! ------------
    3840!> Plot output of 1D-profiles for PROFIL
    39 !------------------------------------------------------------------------------!
     41!--------------------------------------------------------------------------------------------------!
    4042 SUBROUTINE data_output_profiles
    41  
    42 
    43     USE control_parameters,                                                    &
    44         ONLY:  average_count_pr, averaging_interval_pr, coupling_start_time,   &
    45                dopr_n, dopr_time_count, normalizing_region,                    &
    46                time_since_reference_point
    47 
    48     USE cpulog,                                                                &
     43
     44
     45    USE control_parameters,                                                                        &
     46        ONLY:  average_count_pr, averaging_interval_pr, coupling_start_time,                       &
     47               dopr_n, dopr_time_count, normalizing_region, time_since_reference_point
     48
     49    USE cpulog,                                                                                    &
    4950        ONLY:  cpu_log, log_point
    5051
    51     USE indices,                                                               &
     52    USE indices,                                                                                   &
    5253        ONLY:  nzb, nzt
    5354
     
    5859#endif
    5960
    60     USE netcdf_interface,                                                      &
    61         ONLY:  id_set_pr, id_var_dopr, id_var_norm_dopr, id_var_time_pr,       &
    62                nc_stat, netcdf_handle_error, output_for_t0
     61    USE netcdf_interface,                                                                          &
     62        ONLY:  id_set_pr, id_var_dopr, id_var_norm_dopr, id_var_time_pr, nc_stat,                  &
     63               netcdf_handle_error, output_for_t0
    6364
    6465    USE pegrid
     
    6667    USE profil_parameter
    6768
    68     USE statistics,                                                            &
     69    USE statistics,                                                                                &
    6970        ONLY:  flow_statistics_called, hom, hom_sum, pr_palm, statistic_regions
    7071
     
    9293       ELSE
    9394!
    94 !--       This case may happen if dt_dopr is changed in the
    95 !--       runtime_parameters-list of a restart run
     95!--       This case may happen if dt_dopr is changed in the runtime_parameters-list of a restart run
    9696          RETURN
    9797       ENDIF
    9898    ENDIF
    9999
    100    
     100
    101101    IF ( myid == 0 )  THEN
    102102
     
    115115!--    Output of initial profiles
    116116       IF ( dopr_time_count == 1 )  THEN
    117        
    118           IF ( .NOT. output_for_t0 ) THEN
    119 
    120 #if defined( __netcdf )         
    121 !
    122 !--          Store initial time to time axis, but only if an output
    123 !--          is required for at least one of the profiles. The initial time
    124 !--          is either 0, or, in case of a prerun for coupled atmosphere-ocean
    125 !--          runs, has a negative value
     117
     118          IF ( .NOT. output_for_t0 ) THEN
     119
     120#if defined( __netcdf )
     121!
     122!--          Store initial time to time axis, but only if an output is required for at least one of
     123!--          the profiles. The initial time is either 0, or, in case of a prerun for coupled
     124!--          atmosphere-ocean runs, has a negative value
    126125             DO  i = 1, dopr_n
    127126                IF ( dopr_initial_index(i) /= 0 )  THEN
    128                    nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,          &
    129                                         (/ -coupling_start_time /),            &
    130                                         start = (/ 1 /), count = (/ 1 /) )
     127                   nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,                              &
     128                                           (/ -coupling_start_time /),                             &
     129                                           start = (/ 1 /), count = (/ 1 /) )
    131130                   CALL netcdf_handle_error( 'data_output_profiles', 329 )
    132131                   output_for_t0 = .TRUE.
     
    138137!--          Store normalization factors
    139138             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), & ! wpt0
    140                                   (/ hom_sum(nzb,18,normalizing_region) /), &
     139                                     (/ hom_sum(nzb,18,normalizing_region) /),                    &
    141140                                     start = (/ 1 /), count = (/ 1 /) )
    142141             CALL netcdf_handle_error( 'data_output_profiles', 330 )
    143142
    144143             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), & ! ws2
    145                         (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
     144                                     (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /),          &
    146145                                     start = (/ 1 /), count = (/ 1 /) )
    147146             CALL netcdf_handle_error( 'data_output_profiles', 331 )
    148147             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), & ! tsw2
    149                         (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
    150                                   start = (/ 1 /), count = (/ 1 /) )
     148                                     (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /),          &
     149                                      start = (/ 1 /), count = (/ 1 /) )
    151150             CALL netcdf_handle_error( 'data_output_profiles', 332 )
    152151             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), & ! ws3
    153                         (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
     152                                     (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /),          &
    154153                                     start = (/ 1 /), count = (/ 1 /) )
    155154             CALL netcdf_handle_error( 'data_output_profiles', 333 )
    156155
    157              nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &!ws2tsw
    158                         (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
    159                            hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
     156             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), & ! ws2tsw
     157                                     (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *             &
     158                                        hom_sum(nzb+3,pr_palm,normalizing_region)    /),          &
    160159                                     start = (/ 1 /), count = (/ 1 /) )
    161160             CALL netcdf_handle_error( 'data_output_profiles', 334 )
    162161
    163              nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &!wstsw2
    164                         (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
    165                            hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
     162             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), & ! wstsw2
     163                                     (/ hom_sum(nzb+8,pr_palm,normalizing_region) *                &
     164                                        hom_sum(nzb+3,pr_palm,normalizing_region)**2 /),          &
    166165                                     start = (/ 1 /), count = (/ 1 /) )
    167166             CALL netcdf_handle_error( 'data_output_profiles', 335 )
    168167
    169168             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), & ! z_i
    170                            (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
     169                                     (/ hom_sum(nzb+6,pr_palm,normalizing_region) /),              &
    171170                                     start = (/ 1 /), count = (/ 1 /) )
    172171             CALL netcdf_handle_error( 'data_output_profiles', 336 )
    173              
     172
    174173#endif
    175174!
     
    186185!
    187186!--                   Write data to netcdf file
    188                       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),    &
    189                                     hom(nzb:nzt+1,1,dopr_initial_index(i),sr), &
    190                                               start = (/ 1, 1 /),              &
     187                      nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),                        &
     188                                              hom(nzb:nzt+1,1,dopr_initial_index(i),sr),          &
     189                                              start = (/ 1, 1 /),                                  &
    191190                                              count = (/ nzt-nzb+2, 1 /) )
    192191                      CALL netcdf_handle_error( 'data_output_profiles', 337 )
     
    210209!
    211210!--    Store time to time axis
    212        nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,        &
    213                                (/ time_since_reference_point /), &
    214                                start = (/ dopr_time_count /),    &
     211       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,                                          &
     212                               (/ time_since_reference_point /),                                   &
     213                               start = (/ dopr_time_count /),                                      &
    215214                               count = (/ 1 /) )
    216215       CALL netcdf_handle_error( 'data_output_profiles', 338 )
     
    219218!--    Store normalization factors
    220219       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), &  ! wpt0
    221                                (/ hom_sum(nzb,18,normalizing_region) /), &
     220                               (/ hom_sum(nzb,18,normalizing_region) /),                           &
     221                               start = (/ dopr_time_count /),                                      &
     222                               count = (/ 1 /) )
     223       CALL netcdf_handle_error( 'data_output_profiles', 339 )
     224
     225       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), &  ! ws2
     226                               (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /),                 &
     227                               start = (/ dopr_time_count /),                                      &
     228                               count = (/ 1 /) )
     229       CALL netcdf_handle_error( 'data_output_profiles', 340 )
     230
     231       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), &  ! tsw2
     232                               (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /),                 &
     233                               start = (/ dopr_time_count /),                                      &
     234                               count = (/ 1 /) )
     235       CALL netcdf_handle_error( 'data_output_profiles', 341 )
     236
     237       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), &  ! ws3
     238                               (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /),                 &
     239                               start = (/ dopr_time_count /),                                      &
     240                               count = (/ 1 /) )
     241       CALL netcdf_handle_error( 'data_output_profiles', 342 )
     242
     243       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &  ! ws2tsw
     244                               (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *                   &
     245                                  hom_sum(nzb+3,pr_palm,normalizing_region) /),                    &
    222246                               start = (/ dopr_time_count /),               &
    223247                               count = (/ 1 /) )
    224        CALL netcdf_handle_error( 'data_output_profiles', 339 )
    225 
    226        nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), &  ! ws2
    227                      (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
    228                                start = (/ dopr_time_count /),               &
    229                                count = (/ 1 /) )
    230        CALL netcdf_handle_error( 'data_output_profiles', 340 )
    231 
    232        nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), &  ! tsw2
    233                      (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
    234                                start = (/ dopr_time_count /),               &
    235                                count = (/ 1 /) )
    236        CALL netcdf_handle_error( 'data_output_profiles', 341 )
    237 
    238        nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), &  ! ws3
    239                      (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
    240                                start = (/ dopr_time_count /),               &
    241                                count = (/ 1 /) )
    242        CALL netcdf_handle_error( 'data_output_profiles', 342 )
    243 
    244        nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &  ! ws2tsw
    245                      (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
    246                         hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
    247                                start = (/ dopr_time_count /),               &
    248                                count = (/ 1 /) )
    249248       CALL netcdf_handle_error( 'data_output_profiles', 343 )
    250249
    251250       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &  ! wstsw2
    252                      (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
    253                         hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
    254                                start = (/ dopr_time_count /),               &
     251                               (/ hom_sum(nzb+8,pr_palm,normalizing_region) *                      &
     252                                  hom_sum(nzb+3,pr_palm,normalizing_region)**2 /),                &
     253                               start = (/ dopr_time_count /),                                      &
    255254                               count = (/ 1 /) )
    256255       CALL netcdf_handle_error( 'data_output_profiles', 344 )
    257256
    258257       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), &  ! z_i
    259                         (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
    260                                start = (/ dopr_time_count /),               &
     258                               (/ hom_sum(nzb+6,pr_palm,normalizing_region) /),                    &
     259                               start = (/ dopr_time_count /),                                      &
    261260                               count = (/ 1 /) )
    262261       CALL netcdf_handle_error( 'data_output_profiles', 345 )
     
    274273!
    275274!--          Write data to netcdf file
    276              nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),          &
    277                                      hom_sum(nzb:nzt+1,dopr_index(i),sr),&
    278                                      start = (/ 1, dopr_time_count /),      &
     275             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),                                 &
     276                                     hom_sum(nzb:nzt+1,dopr_index(i),sr),                          &
     277                                     start = (/ 1, dopr_time_count /),                             &
    279278                                     count = (/ nzt-nzb+2, 1 /) )
    280279             CALL netcdf_handle_error( 'data_output_profiles', 346 )
Note: See TracChangeset for help on using the changeset viewer.