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_3d.f90

    r1321 r1327  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! parts concerning avs output removed,
     23! -netcdf output queries
    2324!
    2425! Former revisions:
     
    8788       
    8889    USE control_parameters,                                                    &
    89         ONLY:  avs_data_file,avs_output, cloud_physics, do3d, do3d_avs_n,      &
    90                do3d_compress, do3d_no, do3d_time_count, io_blocks, io_group,   &
    91                message_string, netcdf_output, netcdf_data_format, ntdim_3d,    &
     90        ONLY:  avs_data_file, cloud_physics, do3d, do3d_avs_n,                 &
     91               do3d_no, do3d_time_count, io_blocks, io_group,                  &
     92               message_string, netcdf_data_format, ntdim_3d,                   &
    9293               nz_do3d, plot_3d_precision, psolver, simulated_time,            &
    9394               simulated_time_chr, skip_do_avs, time_since_reference_point
     
    164165!-- and/or avs).
    165166!-- For netCDF4/HDF5 output, data is written in parallel into one file.
    166     IF ( netcdf_output )  THEN
    167        IF ( netcdf_data_format < 5 )  THEN
    168           CALL check_open( 30 )
    169           IF ( myid == 0 )  CALL check_open( 106+av*10 )
    170        ELSE
    171           CALL check_open( 106+av*10 )
    172        ENDIF
     167    IF ( netcdf_data_format < 5 )  THEN
     168       CALL check_open( 30 )
     169       IF ( myid == 0 )  CALL check_open( 106+av*10 )
    173170    ELSE
    174        IF ( avs_output  .OR.  ( numprocs > 1 ) )  CALL check_open( 30 )
     171       CALL check_open( 106+av*10 )
    175172    ENDIF
    176173
     
    186183    do3d_time_count(av) = do3d_time_count(av) + 1
    187184    IF ( myid == 0 )  THEN
    188        IF ( netcdf_output )  THEN
    189           nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_time_3d(av),           &
    190                                   (/ time_since_reference_point /),            &
    191                                   start = (/ do3d_time_count(av) /),           &
    192                                   count = (/ 1 /) )
    193           CALL handle_netcdf_error( 'data_output_3d', 376 )
    194        ENDIF
     185       nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_time_3d(av),           &
     186                               (/ time_since_reference_point /),            &
     187                               start = (/ do3d_time_count(av) /),           &
     188                               count = (/ 1 /) )
     189       CALL handle_netcdf_error( 'data_output_3d', 376 )
    195190    ENDIF
    196191#endif
     
    201196
    202197    DO  WHILE ( do3d(av,if)(1:1) /= ' ' )
    203 !
    204 !--    Set the precision for data compression.
    205        IF ( do3d_compress )  THEN
    206           DO  i = 1, 100
    207              IF ( plot_3d_precision(i)%variable == do3d(av,if) )  THEN
    208                 prec = plot_3d_precision(i)%precision
    209                 EXIT
    210              ENDIF
    211           ENDDO
    212        ENDIF
    213 
    214198!
    215199!--    Store the array chosen on the temporary array.
     
    504488
    505489!
    506 !--    Output of the volume data information for the AVS-FLD-file.
    507        do3d_avs_n = do3d_avs_n + 1
    508        IF ( myid == 0  .AND.  avs_output )  THEN
    509 !
    510 !--       AVS-labels must not contain any colons. Hence they must be removed
    511 !--       from the time character string.
    512           simulated_time_mod = simulated_time_chr
    513           DO  WHILE ( SCAN( simulated_time_mod, ':' ) /= 0 )
    514              pos = SCAN( simulated_time_mod, ':' )
    515              simulated_time_mod(pos:pos) = '/'
     490!--    Output of the 3D-array
     491#if defined( __parallel )
     492       IF ( netcdf_data_format < 5 )  THEN
     493!
     494!--       Non-parallel netCDF output. Data is output in parallel in
     495!--       FORTRAN binary format here, and later collected into one file by
     496!--       combine_plot_fields
     497          IF ( myid == 0 )  THEN
     498             WRITE ( 30 )  time_since_reference_point,                   &
     499                           do3d_time_count(av), av
     500          ENDIF
     501          DO  i = 0, io_blocks-1
     502             IF ( i == io_group )  THEN
     503                WRITE ( 30 )  nxlg, nxrg, nysg, nyng, nzb, nz_do3d
     504                WRITE ( 30 )  local_pf
     505             ENDIF
     506#if defined( __parallel )
     507             CALL MPI_BARRIER( comm2d, ierr )
     508#endif
    516509          ENDDO
    517510
    518           IF ( av == 0 )  THEN
    519              WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ),            &
    520                                  skip_do_avs, TRIM( do3d(av,if) ),             &
    521                                  TRIM( simulated_time_mod )
     511       ELSE
     512#if defined( __netcdf )
     513!
     514!--       Parallel output in netCDF4/HDF5 format.
     515!--       Do not output redundant ghost point data except for the
     516!--       boundaries of the total domain.
     517          IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     518             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     519                               local_pf(nxl:nxr+1,nys:nyn,nzb:nz_do3d),  &
     520                start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
     521                count = (/ nxr-nxl+2, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
     522          ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     523             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     524                               local_pf(nxl:nxr,nys:nyn+1,nzb:nz_do3d),  &
     525                start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
     526                count = (/ nxr-nxl+1, nyn-nys+2, nz_do3d-nzb+1, 1 /) )
     527          ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     528             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     529                             local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),  &
     530                start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
     531                count = (/ nxr-nxl+2, nyn-nys+2, nz_do3d-nzb+1, 1 /) )
    522532          ELSE
    523              WRITE ( 33, 3300 )  do3d_avs_n, TRIM( avs_data_file ),            &
    524                                  skip_do_avs, TRIM( do3d(av,if) ) //           &
    525                                  ' averaged', TRIM( simulated_time_mod )
     533             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
     534                                 local_pf(nxl:nxr,nys:nyn,nzb:nz_do3d),  &
     535                start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
     536                count = (/ nxr-nxl+1, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
    526537          ENDIF
    527 !
    528 !--       Determine the Skip-value for the next array. Record end and start
    529 !--       require 4 byte each.
    530           skip_do_avs = skip_do_avs + ( ( ( nx+2*nbgp ) * ( ny+2*nbgp ) *      &
    531                                           ( nz_do3d+1 ) ) * 4 + 8 )
     538          CALL handle_netcdf_error( 'data_output_3d', 386 )
     539#endif
    532540       ENDIF
    533 
    534 !
    535 !--    Output of the 3D-array. (compressed/uncompressed)
    536        IF ( do3d_compress )  THEN
    537 !
    538 !--       Compression, output of compression information on FLD-file and output
    539 !--       of compressed data.
    540           CALL write_compressed( local_pf, 30, 33, myid, nxl, nxr, nyn, nys,   &
    541                                  nzb, nz_do3d, prec, nbgp )
    542        ELSE
    543 !
    544 !--       Uncompressed output.
    545 #if defined( __parallel )
    546           IF ( netcdf_output )  THEN
    547              IF ( netcdf_data_format < 5 )  THEN
    548 !
    549 !--             Non-parallel netCDF output. Data is output in parallel in
    550 !--             FORTRAN binary format here, and later collected into one file by
    551 !--             combine_plot_fields
    552                 IF ( myid == 0 )  THEN
    553                    WRITE ( 30 )  time_since_reference_point,                   &
    554                                  do3d_time_count(av), av
    555                 ENDIF
    556                 DO  i = 0, io_blocks-1
    557                    IF ( i == io_group )  THEN
    558                       WRITE ( 30 )  nxlg, nxrg, nysg, nyng, nzb, nz_do3d
    559                       WRITE ( 30 )  local_pf
    560                    ENDIF
    561 #if defined( __parallel )
    562                    CALL MPI_BARRIER( comm2d, ierr )
    563 #endif
    564                 ENDDO
    565 
    566              ELSE
     541#else
    567542#if defined( __netcdf )
    568 !
    569 !--             Parallel output in netCDF4/HDF5 format.
    570 !--             Do not output redundant ghost point data except for the
    571 !--             boundaries of the total domain.
    572                 IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    573                    nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
    574                                      local_pf(nxl:nxr+1,nys:nyn,nzb:nz_do3d),  &
    575                       start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
    576                       count = (/ nxr-nxl+2, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
    577                 ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    578                    nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
    579                                      local_pf(nxl:nxr,nys:nyn+1,nzb:nz_do3d),  &
    580                       start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
    581                       count = (/ nxr-nxl+1, nyn-nys+2, nz_do3d-nzb+1, 1 /) )
    582                 ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    583                    nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
    584                                    local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),  &
    585                       start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
    586                       count = (/ nxr-nxl+2, nyn-nys+2, nz_do3d-nzb+1, 1 /) )
    587                 ELSE
    588                    nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),  &
    589                                        local_pf(nxl:nxr,nys:nyn,nzb:nz_do3d),  &
    590                       start = (/ nxl+1, nys+1, nzb+1, do3d_time_count(av) /),  &
    591                       count = (/ nxr-nxl+1, nyn-nys+1, nz_do3d-nzb+1, 1 /) )
    592                 ENDIF
    593                 CALL handle_netcdf_error( 'data_output_3d', 386 )
    594 #endif
    595              ENDIF
    596           ENDIF
    597 #else
    598           IF ( avs_output )  THEN
    599              WRITE ( 30 )  local_pf(nxl:nxr+1,nys:nyn+1,:)
    600           ENDIF
    601 #if defined( __netcdf )
    602           IF ( netcdf_output )  THEN
    603 
    604              nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),        &
    605                                local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),      &
    606                                start = (/ 1, 1, 1, do3d_time_count(av) /),     &
    607                                count = (/ nx+2, ny+2, nz_do3d-nzb+1, 1 /) )
    608              CALL handle_netcdf_error( 'data_output_3d', 446 )
    609 
    610           ENDIF
     543       nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,if),        &
     544                         local_pf(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d),      &
     545                         start = (/ 1, 1, 1, do3d_time_count(av) /),     &
     546                         count = (/ nx+2, ny+2, nz_do3d-nzb+1, 1 /) )
     547       CALL handle_netcdf_error( 'data_output_3d', 446 )
    611548#endif
    612549#endif
    613        ENDIF
    614550
    615551       if = if + 1
Note: See TracChangeset for help on using the changeset viewer.