Ignore:
Timestamp:
Mar 21, 2014 11:00:16 AM (10 years ago)
Author:
raasch
Message:

Changed:


-s real64 removed (.mrun.config.hlrnIII)
-r8 removed (.mrun.config.imuk)
deleted: .mrun.config.imuk_ice2_netcdf4 .mrun.config.imuk_hlrn

REAL constants defined as wp-kind in modules

"baroclinicity" renamed "baroclinity", "ocean version" replaced by
"ocean mode"

code parts concerning old output formats "iso2d" and "avs" removed.
netCDF is the only remaining output format.

Errors:


bugfix: duplicate error message 56 removed

File:
1 edited

Legend:

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

    r1323 r1327  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! -netcdf output queries
    2323!
    2424! Former revisions:
     
    6565    USE control_parameters,                                                    &
    6666        ONLY:  average_count_pr, averaging_interval_pr, coupling_start_time,   &
    67                dopr_n, dopr_time_count, netcdf_output, normalizing_region,     &
     67               dopr_n, dopr_time_count, normalizing_region,                    &
    6868               time_since_reference_point
    6969
     
    122122!
    123123!--    Open file for profile output in NetCDF format
    124        IF ( netcdf_output )  THEN
    125           CALL check_open( 104 )
    126        ENDIF
     124       CALL check_open( 104 )
    127125
    128126!
     
    136134          IF ( .NOT. output_for_t0 ) THEN
    137135
    138              IF ( netcdf_output )  THEN
    139136#if defined( __netcdf )         
    140137!
    141 !--             Store initial time to time axis, but only if an output
    142 !--             is required for at least one of the profiles. The initial time
    143 !--             is either 0, or, in case of a prerun for coupled atmosphere-ocean
    144 !--             runs, has a negative value
    145                 DO  i = 1, dopr_n
    146                 IF ( dopr_initial_index(i) /= 0 )  THEN
    147                    nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,  &
    148                                            (/ -coupling_start_time /), &
    149                                            start = (/ 1 /), count = (/ 1 /) )
    150                       CALL handle_netcdf_error( 'data_output_profiles', 329 )
    151                       output_for_t0 = .TRUE.
    152                       EXIT
    153                    ENDIF
    154                 ENDDO
    155 
    156 !
    157 !--             Store normalization factors
    158                 nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), & ! wpt0
    159                                      (/ hom_sum(nzb,18,normalizing_region) /), &
     138!--          Store initial time to time axis, but only if an output
     139!--          is required for at least one of the profiles. The initial time
     140!--          is either 0, or, in case of a prerun for coupled atmosphere-ocean
     141!--          runs, has a negative value
     142             DO  i = 1, dopr_n
     143             IF ( dopr_initial_index(i) /= 0 )  THEN
     144                nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,  &
     145                                        (/ -coupling_start_time /), &
    160146                                        start = (/ 1 /), count = (/ 1 /) )
    161                 CALL handle_netcdf_error( 'data_output_profiles', 330 )
    162 
    163                 nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), & ! ws2
    164                            (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
    165                                         start = (/ 1 /), count = (/ 1 /) )
    166                 CALL handle_netcdf_error( 'data_output_profiles', 331 )
    167                 nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), & ! tsw2
    168                            (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
    169                                      start = (/ 1 /), count = (/ 1 /) )
    170                 CALL handle_netcdf_error( 'data_output_profiles', 332 )
    171                 nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), & ! ws3
    172                            (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
    173                                         start = (/ 1 /), count = (/ 1 /) )
    174                 CALL handle_netcdf_error( 'data_output_profiles', 333 )
    175 
    176                 nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &!ws2tsw
    177                            (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
    178                               hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
    179                                         start = (/ 1 /), count = (/ 1 /) )
    180                 CALL handle_netcdf_error( 'data_output_profiles', 334 )
    181 
    182                 nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &!wstsw2
    183                            (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
    184                               hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
    185                                         start = (/ 1 /), count = (/ 1 /) )
    186                 CALL handle_netcdf_error( 'data_output_profiles', 335 )
    187 
    188                 nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), & ! z_i
    189                               (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
    190                                         start = (/ 1 /), count = (/ 1 /) )
    191                 CALL handle_netcdf_error( 'data_output_profiles', 336 )
     147                   CALL handle_netcdf_error( 'data_output_profiles', 329 )
     148                   output_for_t0 = .TRUE.
     149                   EXIT
     150                ENDIF
     151             ENDDO
     152
     153!
     154!--          Store normalization factors
     155             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), & ! wpt0
     156                                  (/ hom_sum(nzb,18,normalizing_region) /), &
     157                                     start = (/ 1 /), count = (/ 1 /) )
     158             CALL handle_netcdf_error( 'data_output_profiles', 330 )
     159
     160             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), & ! ws2
     161                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
     162                                     start = (/ 1 /), count = (/ 1 /) )
     163             CALL handle_netcdf_error( 'data_output_profiles', 331 )
     164             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), & ! tsw2
     165                        (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
     166                                  start = (/ 1 /), count = (/ 1 /) )
     167             CALL handle_netcdf_error( 'data_output_profiles', 332 )
     168             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), & ! ws3
     169                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
     170                                     start = (/ 1 /), count = (/ 1 /) )
     171             CALL handle_netcdf_error( 'data_output_profiles', 333 )
     172
     173             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &!ws2tsw
     174                        (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
     175                           hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
     176                                     start = (/ 1 /), count = (/ 1 /) )
     177             CALL handle_netcdf_error( 'data_output_profiles', 334 )
     178
     179             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &!wstsw2
     180                        (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
     181                           hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
     182                                     start = (/ 1 /), count = (/ 1 /) )
     183             CALL handle_netcdf_error( 'data_output_profiles', 335 )
     184
     185             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), & ! z_i
     186                           (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
     187                                     start = (/ 1 /), count = (/ 1 /) )
     188             CALL handle_netcdf_error( 'data_output_profiles', 336 )
    192189             
    193190#endif
    194              ENDIF
    195191!
    196192!--          Loop over all 1D variables
     
    203199                   DO  sr = 0, statistic_regions
    204200
    205                       IF ( netcdf_output )  THEN
    206201#if defined( __netcdf )
    207202!
    208 !--                      Write data to netcdf file
    209                          nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),    &
    210                                        hom(nzb:nzt+1,1,dopr_initial_index(i),sr), &
    211                                                  start = (/ 1, 1 /),              &
    212                                                  count = (/ nzt-nzb+2, 1 /) )
    213                          CALL handle_netcdf_error( 'data_output_profiles', 337 )
     203!--                   Write data to netcdf file
     204                      nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),    &
     205                                    hom(nzb:nzt+1,1,dopr_initial_index(i),sr), &
     206                                              start = (/ 1, 1 /),              &
     207                                              count = (/ nzt-nzb+2, 1 /) )
     208                      CALL handle_netcdf_error( 'data_output_profiles', 337 )
    214209#endif
    215                       ENDIF
    216210
    217211                   ENDDO
     
    221215             ENDDO   ! Loop over dopr_n for initial profiles
    222216
    223              IF ( netcdf_output  .AND.  output_for_t0 )  THEN
     217             IF ( output_for_t0 )  THEN
    224218                dopr_time_count = dopr_time_count + 1
    225219             ENDIF
     
    228222       ENDIF   ! Initial profiles
    229223
    230        IF ( netcdf_output )  THEN
    231224#if defined( __netcdf )
    232225
    233226!
    234 !--       Store time to time axis         
    235           nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,        &
    236                                   (/ time_since_reference_point /), &
    237                                   start = (/ dopr_time_count /),    &
    238                                   count = (/ 1 /) )
    239           CALL handle_netcdf_error( 'data_output_profiles', 338 )
    240 
    241 !
    242 !--       Store normalization factors
    243           nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), &  ! wpt0
    244                                   (/ hom_sum(nzb,18,normalizing_region) /), &
    245                                   start = (/ dopr_time_count /),               &
    246                                   count = (/ 1 /) )
    247           CALL handle_netcdf_error( 'data_output_profiles', 339 )
    248 
    249           nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), &  ! ws2
    250                         (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
    251                                   start = (/ dopr_time_count /),               &
    252                                   count = (/ 1 /) )
    253           CALL handle_netcdf_error( 'data_output_profiles', 340 )
    254 
    255           nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), &  ! tsw2
    256                         (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
    257                                   start = (/ dopr_time_count /),               &
    258                                   count = (/ 1 /) )
    259           CALL handle_netcdf_error( 'data_output_profiles', 341 )
    260 
    261           nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), &  ! ws3
    262                         (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
    263                                   start = (/ dopr_time_count /),               &
    264                                   count = (/ 1 /) )
    265           CALL handle_netcdf_error( 'data_output_profiles', 342 )
    266 
    267           nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &  ! ws2tsw
    268                         (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
    269                            hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
    270                                   start = (/ dopr_time_count /),               &
    271                                   count = (/ 1 /) )
    272           CALL handle_netcdf_error( 'data_output_profiles', 343 )
    273          
    274           nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &  ! wstsw2
    275                         (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
    276                            hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
    277                                   start = (/ dopr_time_count /),               &
    278                                   count = (/ 1 /) )
    279           CALL handle_netcdf_error( 'data_output_profiles', 344 )
    280 
    281           nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), &  ! z_i
    282                            (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
    283                                   start = (/ dopr_time_count /),               &
    284                                   count = (/ 1 /) )
    285           CALL handle_netcdf_error( 'data_output_profiles', 345 )
     227!--    Store time to time axis
     228       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,        &
     229                               (/ time_since_reference_point /), &
     230                               start = (/ dopr_time_count /),    &
     231                               count = (/ 1 /) )
     232       CALL handle_netcdf_error( 'data_output_profiles', 338 )
     233
     234!
     235!--    Store normalization factors
     236       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(1), &  ! wpt0
     237                               (/ hom_sum(nzb,18,normalizing_region) /), &
     238                               start = (/ dopr_time_count /),               &
     239                               count = (/ 1 /) )
     240       CALL handle_netcdf_error( 'data_output_profiles', 339 )
     241
     242       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(2), &  ! ws2
     243                     (/ hom_sum(nzb+8,pr_palm,normalizing_region)**2 /), &
     244                               start = (/ dopr_time_count /),               &
     245                               count = (/ 1 /) )
     246       CALL handle_netcdf_error( 'data_output_profiles', 340 )
     247
     248       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(3), &  ! tsw2
     249                     (/ hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
     250                               start = (/ dopr_time_count /),               &
     251                               count = (/ 1 /) )
     252       CALL handle_netcdf_error( 'data_output_profiles', 341 )
     253
     254       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(4), &  ! ws3
     255                     (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 /), &
     256                               start = (/ dopr_time_count /),               &
     257                               count = (/ 1 /) )
     258       CALL handle_netcdf_error( 'data_output_profiles', 342 )
     259
     260       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(5), &  ! ws2tsw
     261                     (/ hom_sum(nzb+8,pr_palm,normalizing_region)**3 *   &
     262                        hom_sum(nzb+3,pr_palm,normalizing_region)    /), &
     263                               start = (/ dopr_time_count /),               &
     264                               count = (/ 1 /) )
     265       CALL handle_netcdf_error( 'data_output_profiles', 343 )
     266
     267       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(6), &  ! wstsw2
     268                     (/ hom_sum(nzb+8,pr_palm,normalizing_region) *      &
     269                        hom_sum(nzb+3,pr_palm,normalizing_region)**2 /), &
     270                               start = (/ dopr_time_count /),               &
     271                               count = (/ 1 /) )
     272       CALL handle_netcdf_error( 'data_output_profiles', 344 )
     273
     274       nc_stat = NF90_PUT_VAR( id_set_pr, id_var_norm_dopr(7), &  ! z_i
     275                        (/ hom_sum(nzb+6,pr_palm,normalizing_region) /), &
     276                               start = (/ dopr_time_count /),               &
     277                               count = (/ 1 /) )
     278       CALL handle_netcdf_error( 'data_output_profiles', 345 )
    286279#endif
    287        ENDIF
    288280
    289281!
     
    295287          DO  sr = 0, statistic_regions
    296288
    297              IF ( netcdf_output )  THEN
    298289#if defined( __netcdf )
    299290!
    300 !--             Write data to netcdf file
    301                 nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),          &
    302                                         hom_sum(nzb:nzt+1,dopr_index(i),sr),&
    303                                         start = (/ 1, dopr_time_count /),      &
    304                                         count = (/ nzt-nzb+2, 1 /) )
    305                 CALL handle_netcdf_error( 'data_output_profiles', 346 )
     291!--          Write data to netcdf file
     292             nc_stat = NF90_PUT_VAR( id_set_pr, id_var_dopr(i,sr),          &
     293                                     hom_sum(nzb:nzt+1,dopr_index(i),sr),&
     294                                     start = (/ 1, dopr_time_count /),      &
     295                                     count = (/ nzt-nzb+2, 1 /) )
     296             CALL handle_netcdf_error( 'data_output_profiles', 346 )
    306297#endif
    307              ENDIF
    308298
    309299          ENDDO
Note: See TracChangeset for help on using the changeset viewer.