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

    r1321 r1327  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! parts concerning iso2d output removed,
     23! -netcdf output queries
    2324!
    2425! Former revisions:
     
    101102               do2d_xz_last_time, do2d_xz_n, do2d_xz_time_count,               &
    102103               do2d_yz_last_time, do2d_yz_n, do2d_yz_time_count,               &
    103                ibc_uv_b, icloud_scheme, io_blocks, io_group, iso2d_output,     &
    104                message_string, netcdf_data_format, netcdf_output,              &
     104               ibc_uv_b, icloud_scheme, io_blocks, io_group,                   &
     105               message_string, netcdf_data_format,                             &
    105106               ntdim_2d_xy, ntdim_2d_xz, ntdim_2d_yz, psolver, section,        &
    106107               simulated_time,  simulated_time_chr, time_since_reference_point
     
    236237!
    237238!--       Parallel netCDF4/HDF5 output is done on all PEs, all other on PE0 only
    238           IF ( netcdf_output .AND. ( myid == 0 .OR. netcdf_data_format > 4 ) ) &
    239           THEN
     239          IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
    240240             CALL check_open( 101+av*10 )
    241241          ENDIF
     
    245245          ELSE
    246246             IF ( myid == 0 )  THEN
    247                 IF ( iso2d_output )  CALL check_open( 21 )
    248247#if defined( __parallel )
    249248                ALLOCATE( total_2d(-nbgp:nx+nbgp,-nbgp:ny+nbgp) )
     
    269268!
    270269!--       Parallel netCDF4/HDF5 output is done on all PEs, all other on PE0 only
    271           IF ( netcdf_output .AND. ( myid == 0 .OR. netcdf_data_format > 4 ) ) &
    272           THEN
     270          IF ( myid == 0 .OR. netcdf_data_format > 4 )  THEN
    273271             CALL check_open( 102+av*10 )
    274272          ENDIF
     
    278276          ELSE
    279277             IF ( myid == 0 )  THEN
    280                 IF ( iso2d_output )  CALL check_open( 22 )
    281278#if defined( __parallel )
    282279                ALLOCATE( total_2d(-nbgp:nx+nbgp,nzb:nzt+1) )
     
    302299!
    303300!--       Parallel netCDF4/HDF5 output is done on all PEs, all other on PE0 only
    304           IF ( netcdf_output .AND. ( myid == 0 .OR. netcdf_data_format > 4 ) ) &
    305           THEN
     301          IF ( myid == 0 .OR. netcdf_data_format > 4 )  THEN
    306302             CALL check_open( 103+av*10 )
    307303          ENDIF
     
    311307          ELSE
    312308             IF ( myid == 0 )  THEN
    313                 IF ( iso2d_output )  CALL check_open( 23 )
    314309#if defined( __parallel )
    315310                ALLOCATE( total_2d(-nbgp:ny+nbgp,nzb:nzt+1) )
     
    882877                      do2d_xy_last_time(av)  = simulated_time
    883878                      IF ( myid == 0 )  THEN
    884                          IF ( ( .NOT. data_output_2d_on_each_pe  .AND.         &
    885                               netcdf_output )  .OR.  netcdf_data_format > 4 )  &
     879                         IF ( .NOT. data_output_2d_on_each_pe  &
     880                              .OR.  netcdf_data_format > 4 )   &
    886881                         THEN
    887882#if defined( __netcdf )
     
    921916
    922917#if defined( __parallel )
    923                    IF ( netcdf_output  .AND.  netcdf_data_format > 4 )  THEN
     918                   IF ( netcdf_data_format > 4 )  THEN
    924919!
    925920!--                   Parallel output in netCDF4/HDF5 format.
     
    947942!--                      Output of partial arrays on each PE
    948943#if defined( __netcdf )
    949                          IF ( netcdf_output  .AND.  myid == 0 )  THEN
     944                         IF ( myid == 0 )  THEN
    950945                            WRITE ( 21 )  time_since_reference_point,          &
    951946                                          do2d_xy_time_count(av), av
     
    994989                            ENDDO
    995990!
    996 !--                         Output of the total cross-section.
    997                             IF ( iso2d_output )  THEN
    998                                WRITE (21)  total_2d(-nbgp:nx+nbgp,-nbgp:ny+nbgp)
    999                             ENDIF
    1000 !
    1001991!--                         Relocate the local array for the next loop increment
    1002992                            DEALLOCATE( local_2d )
     
    1004994
    1005995#if defined( __netcdf )
    1006                             IF ( netcdf_output )  THEN
    1007                                IF ( two_d ) THEN
    1008                                   nc_stat = NF90_PUT_VAR( id_set_xy(av),       &
    1009                                                           id_var_do2d(av,if),  &
    1010                                                       total_2d(0:nx+1,0:ny+1), &
    1011                                 start = (/ 1, 1, 1, do2d_xy_time_count(av) /), &
    1012                                                 count = (/ nx+2, ny+2, 1, 1 /) )
    1013                                ELSE
    1014                                   nc_stat = NF90_PUT_VAR( id_set_xy(av),       &
    1015                                                           id_var_do2d(av,if),  &
    1016                                                       total_2d(0:nx+1,0:ny+1), &
    1017                                start = (/ 1, 1, is, do2d_xy_time_count(av) /), &
    1018                                                 count = (/ nx+2, ny+2, 1, 1 /) )
    1019                                ENDIF
    1020                                CALL handle_netcdf_error( 'data_output_2d', 54 )
     996                            IF ( two_d ) THEN
     997                               nc_stat = NF90_PUT_VAR( id_set_xy(av),       &
     998                                                       id_var_do2d(av,if),  &
     999                                                   total_2d(0:nx+1,0:ny+1), &
     1000                             start = (/ 1, 1, 1, do2d_xy_time_count(av) /), &
     1001                                             count = (/ nx+2, ny+2, 1, 1 /) )
     1002                            ELSE
     1003                               nc_stat = NF90_PUT_VAR( id_set_xy(av),       &
     1004                                                       id_var_do2d(av,if),  &
     1005                                                   total_2d(0:nx+1,0:ny+1), &
     1006                            start = (/ 1, 1, is, do2d_xy_time_count(av) /), &
     1007                                             count = (/ nx+2, ny+2, 1, 1 /) )
    10211008                            ENDIF
     1009                            CALL handle_netcdf_error( 'data_output_2d', 54 )
    10221010#endif
    10231011
     
    10431031                   ENDIF
    10441032#else
    1045                    IF ( iso2d_output )  THEN
    1046                       WRITE (21)  local_2d(nxl:nxr+1,nys:nyn+1)
     1033#if defined( __netcdf )
     1034                   IF ( two_d ) THEN
     1035                      nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
     1036                                              id_var_do2d(av,if),           &
     1037                                             local_2d(nxl:nxr+1,nys:nyn+1), &
     1038                             start = (/ 1, 1, 1, do2d_xy_time_count(av) /), &
     1039                                           count = (/ nx+2, ny+2, 1, 1 /) )
     1040                   ELSE
     1041                      nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
     1042                                              id_var_do2d(av,if),           &
     1043                                             local_2d(nxl:nxr+1,nys:nyn+1), &
     1044                            start = (/ 1, 1, is, do2d_xy_time_count(av) /), &
     1045                                           count = (/ nx+2, ny+2, 1, 1 /) )
    10471046                   ENDIF
    1048 #if defined( __netcdf )
    1049                    IF ( netcdf_output )  THEN
    1050                       IF ( two_d ) THEN
    1051                          nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
    1052                                                  id_var_do2d(av,if),           &
    1053                                                 local_2d(nxl:nxr+1,nys:nyn+1), &
    1054                                 start = (/ 1, 1, 1, do2d_xy_time_count(av) /), &
    1055                                               count = (/ nx+2, ny+2, 1, 1 /) )
    1056                       ELSE
    1057                          nc_stat = NF90_PUT_VAR( id_set_xy(av),                &
    1058                                                  id_var_do2d(av,if),           &
    1059                                                 local_2d(nxl:nxr+1,nys:nyn+1), &
    1060                                start = (/ 1, 1, is, do2d_xy_time_count(av) /), &
    1061                                               count = (/ nx+2, ny+2, 1, 1 /) )
    1062                       ENDIF
    1063                       CALL handle_netcdf_error( 'data_output_2d', 447 )
    1064                    ENDIF
     1047                   CALL handle_netcdf_error( 'data_output_2d', 447 )
    10651048#endif
    10661049#endif
    10671050                   do2d_xy_n = do2d_xy_n + 1
    1068 !
    1069 !--                Write LOCAL parameter set for ISO2D.
    1070                    IF ( myid == 0  .AND.  iso2d_output )  THEN
    1071                       IF ( section(is,s) /= -1 )  THEN
    1072                          WRITE ( section_chr, '(''z = '',F7.2,'' m  (GP '',I3, &
    1073                                                &'')'')'                        &
    1074                                )  level_z(layer_xy), layer_xy
    1075                       ELSE
    1076                          section_chr = 'averaged along z'
    1077                       ENDIF
    1078                       IF ( av == 0 )  THEN
    1079                          rtext = TRIM( do2d(av,if) ) // '  t = ' //            &
    1080                                  TRIM( simulated_time_chr ) // '  ' //         &
    1081                                  TRIM( section_chr )
    1082                       ELSE
    1083                          rtext = TRIM( do2d(av,if) ) // '  averaged t = ' //   &
    1084                                  TRIM( simulated_time_chr ) // '  ' //         &
    1085                                  TRIM( section_chr )
    1086                       ENDIF
    1087                       WRITE (27,LOCAL)
    1088                    ENDIF
    10891051!
    10901052!--                For 2D-arrays (e.g. u*) only one cross-section is available.
     
    11041066                      do2d_xz_last_time(av)  = simulated_time
    11051067                      IF ( myid == 0 )  THEN
    1106                          IF ( ( .NOT. data_output_2d_on_each_pe  .AND.         &
    1107                               netcdf_output )  .OR.  netcdf_data_format > 4 )  &
     1068                         IF ( .NOT. data_output_2d_on_each_pe  &
     1069                              .OR.  netcdf_data_format > 4 )   &
    11081070                         THEN
    11091071#if defined( __netcdf )
     
    11621124
    11631125#if defined( __parallel )
    1164                    IF ( netcdf_output  .AND.  netcdf_data_format > 4 )  THEN
     1126                   IF ( netcdf_data_format > 4 )  THEN
    11651127!
    11661128!--                   Output in netCDF4/HDF5 format.
     
    11921154!--                      index values.
    11931155#if defined( __netcdf )
    1194                          IF ( netcdf_output  .AND.  myid == 0 )  THEN
     1156                         IF ( myid == 0 )  THEN
    11951157                            WRITE ( 22 )  time_since_reference_point,          &
    11961158                                          do2d_xz_time_count(av), av
     
    12581220                            ENDDO
    12591221!
    1260 !--                         Output of the total cross-section.
    1261                             IF ( iso2d_output )  THEN
    1262                                WRITE (22)  total_2d(-nbgp:nx+nbgp,nzb:nzt+1)
    1263                             ENDIF
    1264 !
    12651222!--                         Relocate the local array for the next loop increment
    12661223                            DEALLOCATE( local_2d )
     
    12681225
    12691226#if defined( __netcdf )
    1270                             IF ( netcdf_output )  THEN
    1271                                nc_stat = NF90_PUT_VAR( id_set_xz(av),          &
    1272                                                     id_var_do2d(av,if),        &
    1273                                                     total_2d(0:nx+1,nzb:nzt+1),&
    1274                                start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
    1275                                                 count = (/ nx+2, 1, nz+2, 1 /) )
    1276                                CALL handle_netcdf_error( 'data_output_2d', 58 )
    1277                             ENDIF
     1227                            nc_stat = NF90_PUT_VAR( id_set_xz(av),          &
     1228                                                 id_var_do2d(av,if),        &
     1229                                                 total_2d(0:nx+1,nzb:nzt+1),&
     1230                            start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
     1231                                             count = (/ nx+2, 1, nz+2, 1 /) )
     1232                            CALL handle_netcdf_error( 'data_output_2d', 58 )
    12781233#endif
    12791234
     
    13101265                   ENDIF
    13111266#else
    1312                    IF ( iso2d_output )  THEN
    1313                       WRITE (22)  local_2d(nxl:nxr+1,nzb:nzt+1)
    1314                    ENDIF
    13151267#if defined( __netcdf )
    1316                    IF ( netcdf_output )  THEN
    1317                       nc_stat = NF90_PUT_VAR( id_set_xz(av),                   &
    1318                                               id_var_do2d(av,if),              &
    1319                                               local_2d(nxl:nxr+1,nzb:nzt+1),   &
    1320                                start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
    1321                                               count = (/ nx+2, 1, nz+2, 1 /) )
    1322                       CALL handle_netcdf_error( 'data_output_2d', 451 )
    1323                    ENDIF
     1268                   nc_stat = NF90_PUT_VAR( id_set_xz(av),                   &
     1269                                           id_var_do2d(av,if),              &
     1270                                           local_2d(nxl:nxr+1,nzb:nzt+1),   &
     1271                            start = (/ 1, is, 1, do2d_xz_time_count(av) /), &
     1272                                           count = (/ nx+2, 1, nz+2, 1 /) )
     1273                   CALL handle_netcdf_error( 'data_output_2d', 451 )
    13241274#endif
    13251275#endif
    13261276                   do2d_xz_n = do2d_xz_n + 1
    1327 !
    1328 !--                Write LOCAL-parameter set for ISO2D.
    1329                    IF ( myid == 0  .AND.  iso2d_output )  THEN
    1330                       IF ( section(is,s) /= -1 )  THEN
    1331                          WRITE ( section_chr, '(''y = '',F8.2,'' m  (GP '',I3, &
    1332                                                &'')'')'                        &
    1333                                )  section(is,s)*dy, section(is,s)
    1334                       ELSE
    1335                          section_chr = 'averaged along y'
    1336                       ENDIF
    1337                       IF ( av == 0 )  THEN
    1338                          rtext = TRIM( do2d(av,if) ) // '  t = ' //            &
    1339                                  TRIM( simulated_time_chr ) // '  ' //         &
    1340                                  TRIM( section_chr )
    1341                       ELSE
    1342                          rtext = TRIM( do2d(av,if) ) // '  averaged t = ' //   &
    1343                                  TRIM( simulated_time_chr ) // '  ' //         &
    1344                                  TRIM( section_chr )
    1345                       ENDIF
    1346                       WRITE (28,LOCAL)
    1347                    ENDIF
    13481277
    13491278                CASE ( 'yz' )
     
    13561285                      do2d_yz_last_time(av)  = simulated_time
    13571286                      IF ( myid == 0 )  THEN
    1358                          IF ( ( .NOT. data_output_2d_on_each_pe  .AND.         &
    1359                               netcdf_output )  .OR.  netcdf_data_format > 4 )  &
     1287                         IF ( .NOT. data_output_2d_on_each_pe  &
     1288                              .OR.  netcdf_data_format > 4 )   &
    13601289                         THEN
    13611290#if defined( __netcdf )
     
    14141343
    14151344#if defined( __parallel )
    1416                    IF ( netcdf_output  .AND.  netcdf_data_format > 4 )  THEN
     1345                   IF ( netcdf_data_format > 4 )  THEN
    14171346!
    14181347!--                   Output in netCDF4/HDF5 format.
     
    14441373!--                      index values.
    14451374#if defined( __netcdf )
    1446                          IF ( netcdf_output  .AND.  myid == 0 )  THEN
     1375                         IF ( myid == 0 )  THEN
    14471376                            WRITE ( 23 )  time_since_reference_point,          &
    14481377                                          do2d_yz_time_count(av), av
     
    15101439                            ENDDO
    15111440!
    1512 !--                         Output of the total cross-section.
    1513                             IF ( iso2d_output )  THEN
    1514                                WRITE (23)  total_2d(0:ny+1,nzb:nzt+1)
    1515                             ENDIF
    1516 !
    15171441!--                         Relocate the local array for the next loop increment
    15181442                            DEALLOCATE( local_2d )
     
    15201444
    15211445#if defined( __netcdf )
    1522                             IF ( netcdf_output )  THEN
    1523                                nc_stat = NF90_PUT_VAR( id_set_yz(av),          &
    1524                                                     id_var_do2d(av,if),        &
    1525                                                     total_2d(0:ny+1,nzb:nzt+1),&
    1526                                start = (/ is, 1, 1, do2d_yz_time_count(av) /), &
    1527                                                 count = (/ 1, ny+2, nz+2, 1 /) )
    1528                                CALL handle_netcdf_error( 'data_output_2d', 61 )
    1529                             ENDIF
     1446                            nc_stat = NF90_PUT_VAR( id_set_yz(av),          &
     1447                                                 id_var_do2d(av,if),        &
     1448                                                 total_2d(0:ny+1,nzb:nzt+1),&
     1449                            start = (/ is, 1, 1, do2d_yz_time_count(av) /), &
     1450                                             count = (/ 1, ny+2, nz+2, 1 /) )
     1451                            CALL handle_netcdf_error( 'data_output_2d', 61 )
    15301452#endif
    15311453
     
    15621484                   ENDIF
    15631485#else
    1564                    IF ( iso2d_output )  THEN
    1565                       WRITE (23)  local_2d(nys:nyn+1,nzb:nzt+1)
    1566                    ENDIF
    15671486#if defined( __netcdf )
    1568                    IF ( netcdf_output )  THEN
    1569                       nc_stat = NF90_PUT_VAR( id_set_yz(av),                   &
    1570                                               id_var_do2d(av,if),              &
    1571                                               local_2d(nys:nyn+1,nzb:nzt+1),   &
    1572                                start = (/ is, 1, 1, do2d_xz_time_count(av) /), &
    1573                                               count = (/ 1, ny+2, nz+2, 1 /) )
    1574                       CALL handle_netcdf_error( 'data_output_2d', 452 )
    1575                    ENDIF
     1487                   nc_stat = NF90_PUT_VAR( id_set_yz(av),                   &
     1488                                           id_var_do2d(av,if),              &
     1489                                           local_2d(nys:nyn+1,nzb:nzt+1),   &
     1490                            start = (/ is, 1, 1, do2d_xz_time_count(av) /), &
     1491                                           count = (/ 1, ny+2, nz+2, 1 /) )
     1492                   CALL handle_netcdf_error( 'data_output_2d', 452 )
    15761493#endif
    15771494#endif
    15781495                   do2d_yz_n = do2d_yz_n + 1
    1579 !
    1580 !--                Write LOCAL-parameter set for ISO2D.
    1581                    IF ( myid == 0  .AND.  iso2d_output )  THEN
    1582                       IF ( section(is,s) /= -1 )  THEN
    1583                          WRITE ( section_chr, '(''x = '',F8.2,'' m  (GP '',I3, &
    1584                                                &'')'')'                        &
    1585                                )  section(is,s)*dx, section(is,s)
    1586                       ELSE
    1587                          section_chr = 'averaged along x'
    1588                       ENDIF
    1589                       IF ( av == 0 )  THEN
    1590                          rtext = TRIM( do2d(av,if) ) // '  t = ' //            &
    1591                                  TRIM( simulated_time_chr ) // '  ' //         &
    1592                                  TRIM( section_chr )
    1593                       ELSE
    1594                          rtext = TRIM( do2d(av,if) ) // '  averaged t = ' //   &
    1595                                  TRIM( simulated_time_chr ) // '  ' //         &
    1596                                  TRIM( section_chr )
    1597                       ENDIF
    1598                       WRITE (29,LOCAL)
    1599                    ENDIF
    16001496
    16011497             END SELECT
     
    16091505!--       the performance of the parallel output.
    16101506#if defined( __netcdf )
    1611           IF ( netcdf_output .AND. netcdf_data_format > 4 )  THEN
     1507          IF ( netcdf_data_format > 4 )  THEN
    16121508
    16131509                SELECT CASE ( mode )
Note: See TracChangeset for help on using the changeset viewer.