Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

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

    r1319 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    6571! +z0h
    6672!
    67 ! 790 2011-11-29 03:11:20Z raasch
    68 ! bugfix: calculation of 'pr' must depend on the particle weighting factor
    69 !
    70 ! 771 2011-10-27 10:56:21Z heinze
    71 ! +lpt
    72 !
    73 ! 759 2011-09-15 13:58:31Z raasch
    74 ! Splitting of parallel I/O
    75 !
    76 ! 729 2011-05-26 10:33:34Z heinze
    77 ! Exchange ghost layers for p regardless of used pressure solver (except SOR).
    78 !
    79 ! 691 2011-03-04 08:45:30Z maronga
    80 ! Replaced simulated_time by time_since_reference_point
    81 !
    82 ! 673 2011-01-18 16:19:48Z suehring
    83 ! When using Multigrid or SOR solver an additional CALL exchange_horiz is
    84 ! is needed for pressure output.
    85 !
    86 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    87 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
    88 ! allocation of arrays local_2d and total_2d.
    89 ! Calls of exchange_horiz are modiefied.
    90 !
    91 ! 622 2010-12-10 08:08:13Z raasch
    92 ! optional barriers included in order to speed up collective operations
    93 !
    94 ! 493 2010-03-01 08:30:24Z raasch
    95 ! netCDF4 support (parallel output)
    96 !
    97 ! 367 2009-08-25 08:35:52Z maronga
    98 ! simulated_time in netCDF output replaced by time_since_reference_point.
    99 ! Output of netCDF messages with aid of message handling routine.
    100 ! Bugfix: averaging along z is not allowed for 2d quantities (e.g. u* and z0)
    101 ! Output of messages replaced by message handling routine.
    102 ! Output of user defined 2D (XY) arrays at z=nzb+1 is now possible
    103 ! Bugfix: to_be_resorted => s_av for time-averaged scalars
    104 ! Calculation of shf* and qsws* added.
    105 !
    106 ! 215 2008-11-18 09:54:31Z raasch
    107 ! Bugfix: no output of particle concentration and radius unless particles
    108 ! have been started
    109 !
    110 ! 96 2007-06-04 08:07:41Z raasch
    111 ! Output of density and salinity
    112 !
    113 ! 75 2007-03-22 09:54:05Z raasch
    114 ! Output of precipitation amount/rate and roughness length,
    115 ! 2nd+3rd argument removed from exchange horiz
    116 !
    117 ! RCS Log replace by Id keyword, revision history cleaned up
    118 !
    119 ! Revision 1.5  2006/08/22 13:50:29  raasch
    120 ! xz and yz cross sections now up to nzt+1
    121 !
    122 ! Revision 1.2  2006/02/23 10:19:22  raasch
    123 ! Output of time-averaged data, output of averages along x, y, or z,
    124 ! output of user-defined quantities,
    125 ! section data are copied from local_pf to local_2d before they are output,
    126 ! output of particle concentration and mean radius,
    127 ! Former subroutine plot_2d renamed data_output_2d, pl2d.. renamed do2d..,
    128 ! anz renamed ngp, ebene renamed section, pl2d_.._anz renamed do2d_.._n
    129 !
    13073! Revision 1.1  1997/08/11 06:24:09  raasch
    13174! Initial revision
     
    14083!------------------------------------------------------------------------------!
    14184
    142     USE arrays_3d
     85    USE arrays_3d,                                                             &
     86        ONLY:  dzw, e, nr, p, pt, q, qc, ql, ql_c, ql_v, ql_vp, qr, qsws,      &
     87               rho, sa, shf, tend, ts, u, us, v, vpt, w, z0, z0h, zu, zw
     88       
    14389    USE averaging
    144     USE cloud_parameters
    145     USE control_parameters
    146     USE cpulog
    147     USE grid_variables
    148     USE indices
     90       
     91    USE cloud_parameters,                                                      &
     92        ONLY:  hyrho, l_d_cp, precipitation_amount, precipitation_rate, prr,   &
     93               pt_d_t
     94               
     95    USE control_parameters,                                                    &
     96        ONLY:  cloud_physics, data_output_2d_on_each_pe, data_output_xy,       &
     97               data_output_xz, data_output_yz, do2d,                           &
     98               do2d_xy_last_time, do2d_xy_n, do2d_xy_time_count,               &
     99               do2d_xz_last_time, do2d_xz_n, do2d_xz_time_count,               &
     100               do2d_yz_last_time, do2d_yz_n, do2d_yz_time_count,               &
     101               ibc_uv_b, icloud_scheme, io_blocks, io_group, iso2d_output,     &
     102               message_string, netcdf_data_format, netcdf_output,              &
     103               ntdim_2d_xy, ntdim_2d_xz, ntdim_2d_yz, psolver, section,        &
     104               simulated_time,  simulated_time_chr, time_since_reference_point
     105       
     106    USE cpulog,                                                                &
     107        ONLY:  cpu_log, log_point
     108       
     109    USE grid_variables,                                                        &
     110        ONLY:  dx, dy
     111       
     112    USE indices,                                                               &
     113        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg,       &
     114               nz, nzb, nzt
     115               
     116    USE kinds
     117       
    149118    USE netcdf_control
    150     USE particle_attributes
     119
     120    USE particle_attributes,                                                   &
     121        ONLY:  particle_advection_start, particles, prt_count,                 &
     122               prt_start_index
     123   
    151124    USE pegrid
    152125
    153126    IMPLICIT NONE
    154127
    155     CHARACTER (LEN=2)  ::  do2d_mode, mode
    156     CHARACTER (LEN=4)  ::  grid
    157     CHARACTER (LEN=25) ::  section_chr
    158     CHARACTER (LEN=50) ::  rtext
    159     INTEGER ::  av, ngp, file_id, i, if, is, iis, j, k, l, layer_xy, n, ns, &
    160                 psi, s, sender, &
    161                 ind(4)
    162     LOGICAL ::  found, resorted, two_d
    163     REAL    ::  mean_r, s_r3, s_r4
    164     REAL, DIMENSION(:), ALLOCATABLE ::      level_z
    165     REAL, DIMENSION(:,:), ALLOCATABLE ::    local_2d, local_2d_l
    166     REAL, DIMENSION(:,:,:), ALLOCATABLE ::  local_pf, local_2d_sections, &
    167                                             local_2d_sections_l
     128    CHARACTER (LEN=2)  ::  do2d_mode    !:
     129    CHARACTER (LEN=2)  ::  mode         !:
     130    CHARACTER (LEN=4)  ::  grid         !:
     131    CHARACTER (LEN=25) ::  section_chr  !:
     132    CHARACTER (LEN=50) ::  rtext        !:
     133   
     134    INTEGER(iwp) ::  av        !:
     135    INTEGER(iwp) ::  ngp       !:
     136    INTEGER(iwp) ::  file_id   !:
     137    INTEGER(iwp) ::  i         !:
     138    INTEGER(iwp) ::  if        !:
     139    INTEGER(iwp) ::  is        !:
     140    INTEGER(iwp) ::  iis       !:
     141    INTEGER(iwp) ::  j         !:
     142    INTEGER(iwp) ::  k         !:
     143    INTEGER(iwp) ::  l         !:
     144    INTEGER(iwp) ::  layer_xy  !:
     145    INTEGER(iwp) ::  n         !:
     146    INTEGER(iwp) ::  ns        !:
     147    INTEGER(iwp) ::  psi       !:
     148    INTEGER(iwp) ::  s         !:
     149    INTEGER(iwp) ::  sender    !:
     150    INTEGER(iwp) ::  ind(4)    !:
     151   
     152    LOGICAL ::  found          !:
     153    LOGICAL ::  resorted       !:
     154    LOGICAL ::  two_d          !:
     155   
     156    REAL(wp) ::  mean_r         !:
     157    REAL(wp) ::  s_r3           !:
     158    REAL(wp) ::  s_r4           !:
     159   
     160    REAL(wp), DIMENSION(:), ALLOCATABLE ::      level_z     !:
     161    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::    local_2d    !:
     162    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::    local_2d_l  !:
     163    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf    !:
     164    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_2d_sections   !:
     165    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_2d_sections_l !:
    168166#if defined( __parallel )
    169     REAL, DIMENSION(:,:),   ALLOCATABLE ::  total_2d
    170 #endif
    171     REAL, DIMENSION(:,:,:), POINTER ::  to_be_resorted
     167    REAL(wp), DIMENSION(:,:),   ALLOCATABLE ::  total_2d  !:
     168#endif
     169    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !:
    172170
    173171    NAMELIST /LOCAL/  rtext
     
    184182!-- the given end time by the length of the given output interval.
    185183    IF ( netcdf_data_format > 4 )  THEN
    186        IF ( mode == 'xy'  .AND.  do2d_xy_time_count(av) + 1 > &
     184       IF ( mode == 'xy'  .AND.  do2d_xy_time_count(av) + 1 >                  &
    187185            ntdim_2d_xy(av) )  THEN
    188           WRITE ( message_string, * ) 'Output of xy cross-sections is not ', &
    189                           'given at t=', simulated_time, '&because the', &
     186          WRITE ( message_string, * ) 'Output of xy cross-sections is not ',   &
     187                          'given at t=', simulated_time, '&because the',       &
    190188                          ' maximum number of output time levels is exceeded.'
    191189          CALL message( 'data_output_2d', 'PA0384', 0, 1, 0, 6, 0 )         
    192190          RETURN
    193191       ENDIF
    194        IF ( mode == 'xz'  .AND.  do2d_xz_time_count(av) + 1 > &
     192       IF ( mode == 'xz'  .AND.  do2d_xz_time_count(av) + 1 >                  &
    195193            ntdim_2d_xz(av) )  THEN
    196           WRITE ( message_string, * ) 'Output of xz cross-sections is not ',  &
    197                           'given at t=', simulated_time, '&because the', &
     194          WRITE ( message_string, * ) 'Output of xz cross-sections is not ',   &
     195                          'given at t=', simulated_time, '&because the',       &
    198196                          ' maximum number of output time levels is exceeded.'
    199197          CALL message( 'data_output_2d', 'PA0385', 0, 1, 0, 6, 0 )         
    200198          RETURN
    201199       ENDIF
    202        IF ( mode == 'yz'  .AND.  do2d_yz_time_count(av) + 1 > &
     200       IF ( mode == 'yz'  .AND.  do2d_yz_time_count(av) + 1 >                  &
    203201            ntdim_2d_yz(av) )  THEN
    204           WRITE ( message_string, * ) 'Output of yz cross-sections is not ', &
    205                           'given at t=', simulated_time, '&because the', &
     202          WRITE ( message_string, * ) 'Output of yz cross-sections is not ',   &
     203                          'given at t=', simulated_time, '&because the',       &
    206204                          ' maximum number of output time levels is exceeded.'
    207205          CALL message( 'data_output_2d', 'PA0386', 0, 1, 0, 6, 0 )         
     
    363361                   DO  i = nxlg, nxrg
    364362                      DO  j = nysg, nyng
    365                          local_pf(i,j,nzb+1) = SUM( ql(nzb:nzt,j,i) * &
     363                         local_pf(i,j,nzb+1) = SUM( ql(nzb:nzt,j,i) *          &
    366364                                                    dzw(1:nzt+1) )
    367365                      ENDDO
     
    427425                               s_r4 = 0.0
    428426                               DO  n = psi, psi+prt_count(k,j,i)-1
    429                                   s_r3 = s_r3 + particles(n)%radius**3 * &
     427                                  s_r3 = s_r3 + particles(n)%radius**3 *       &
    430428                                                particles(n)%weight_factor
    431                                   s_r4 = s_r4 + particles(n)%radius**4 * &
     429                                  s_r4 = s_r4 + particles(n)%radius**4 *       &
    432430                                                particles(n)%weight_factor
    433431                               ENDDO
     
    499497                      DO  i = nxlg, nxrg
    500498                         DO  j = nysg, nyng
    501                             local_pf(i,j,nzb+1) = prr_av(nzb+1,j,i) * hyrho(nzb+1)
     499                            local_pf(i,j,nzb+1) = prr_av(nzb+1,j,i) *          &
     500                                                  hyrho(nzb+1)
    502501                         ENDDO
    503502                      ENDDO
     
    539538                      DO  j = nysg, nyng
    540539                            DO  k = nzb, nzt+1
    541                                local_pf(i,j,k) = pt(k,j,i) + l_d_cp *    &
    542                                                              pt_d_t(k) * &
     540                               local_pf(i,j,k) = pt(k,j,i) + l_d_cp *          &
     541                                                             pt_d_t(k) *       &
    543542                                                             ql(k,j,i)
    544543                            ENDDO
     
    600599                               psi = prt_start_index(k,j,i)
    601600                               DO  n = psi, psi+prt_count(k,j,i)-1
    602                                   tend(k,j,i) =  tend(k,j,i) + &
    603                                                  particles(n)%weight_factor / &
     601                                  tend(k,j,i) =  tend(k,j,i) +                 &
     602                                                 particles(n)%weight_factor /  &
    604603                                                 prt_count(k,j,i)
    605604                               ENDDO
     
    824823!
    825824!--             User defined quantity
    826                 CALL user_data_output_2d( av, do2d(av,if), found, grid, &
     825                CALL user_data_output_2d( av, do2d(av,if), found, grid,        &
    827826                                          local_pf, two_d )
    828827                resorted = .TRUE.
     
    837836
    838837                IF ( .NOT. found )  THEN
    839                    message_string = 'no output provided for: ' //    &
     838                   message_string = 'no output provided for: ' //              &
    840839                                    TRIM( do2d(av,if) )
    841840                   CALL message( 'data_output_2d', 'PA0181', 0, 0, 0, 6, 0 )
     
    881880                      do2d_xy_last_time(av)  = simulated_time
    882881                      IF ( myid == 0 )  THEN
    883                          IF ( ( .NOT. data_output_2d_on_each_pe  .AND. &
    884                               netcdf_output )  .OR.  netcdf_data_format > 4 ) &
     882                         IF ( ( .NOT. data_output_2d_on_each_pe  .AND.         &
     883                              netcdf_output )  .OR.  netcdf_data_format > 4 )  &
    885884                         THEN
    886885#if defined( __netcdf )
     
    947946#if defined( __netcdf )
    948947                         IF ( netcdf_output  .AND.  myid == 0 )  THEN
    949                             WRITE ( 21 )  time_since_reference_point, &
     948                            WRITE ( 21 )  time_since_reference_point,          &
    950949                                          do2d_xy_time_count(av), av
    951950                         ENDIF
     
    981980!--                            Index limits are received in arbitrary order from
    982981!--                            the PEs.
    983                                CALL MPI_RECV( ind(1), 4, MPI_INTEGER,    &
    984                                               MPI_ANY_SOURCE, 0, comm2d, &
     982                               CALL MPI_RECV( ind(1), 4, MPI_INTEGER,          &
     983                                              MPI_ANY_SOURCE, 0, comm2d,       &
    985984                                              status, ierr )
    986985                               sender = status(MPI_SOURCE)
    987986                               DEALLOCATE( local_2d )
    988987                               ALLOCATE( local_2d(ind(1):ind(2),ind(3):ind(4)) )
    989                                CALL MPI_RECV( local_2d(ind(1),ind(3)), ngp,  &
    990                                               MPI_REAL, sender, 1, comm2d,   &
     988                               CALL MPI_RECV( local_2d(ind(1),ind(3)), ngp,    &
     989                                              MPI_REAL, sender, 1, comm2d,     &
    991990                                              status, ierr )
    992991                               total_2d(ind(1):ind(2),ind(3):ind(4)) = local_2d
     
    10261025                            ind(1) = nxlg; ind(2) = nxrg
    10271026                            ind(3) = nysg; ind(4) = nyng
    1028                             CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0, &
     1027                            CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0,       &
    10291028                                           comm2d, ierr )
    10301029!
    10311030!--                         Send data to PE0
    1032                             CALL MPI_SEND( local_2d(nxlg,nysg), ngp, &
     1031                            CALL MPI_SEND( local_2d(nxlg,nysg), ngp,           &
    10331032                                           MPI_REAL, 0, 1, comm2d, ierr )
    10341033                         ENDIF
     
    10761075                      ENDIF
    10771076                      IF ( av == 0 )  THEN
    1078                          rtext = TRIM( do2d(av,if) ) // '  t = ' //    &
    1079                                  TRIM( simulated_time_chr ) // '  ' // &
     1077                         rtext = TRIM( do2d(av,if) ) // '  t = ' //            &
     1078                                 TRIM( simulated_time_chr ) // '  ' //         &
    10801079                                 TRIM( section_chr )
    10811080                      ELSE
    1082                          rtext = TRIM( do2d(av,if) ) // '  averaged t = ' // &
    1083                                  TRIM( simulated_time_chr ) // '  ' //       &
     1081                         rtext = TRIM( do2d(av,if) ) // '  averaged t = ' //   &
     1082                                 TRIM( simulated_time_chr ) // '  ' //         &
    10841083                                 TRIM( section_chr )
    10851084                      ENDIF
     
    11031102                      do2d_xz_last_time(av)  = simulated_time
    11041103                      IF ( myid == 0 )  THEN
    1105                          IF ( ( .NOT. data_output_2d_on_each_pe  .AND.        &
    1106                               netcdf_output )  .OR.  netcdf_data_format > 4 ) &
     1104                         IF ( ( .NOT. data_output_2d_on_each_pe  .AND.         &
     1105                              netcdf_output )  .OR.  netcdf_data_format > 4 )  &
    11071106                         THEN
    11081107#if defined( __netcdf )
     
    11301129                         DO  j = nys, nyn
    11311130                            DO  i = nxlg, nxrg
    1132                                local_2d_l(i,k) = local_2d_l(i,k) + &
     1131                               local_2d_l(i,k) = local_2d_l(i,k) +             &
    11331132                                                 local_pf(i,j,k)
    11341133                            ENDDO
     
    11391138!--                   Now do the averaging over all PEs along y
    11401139                      IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    1141                       CALL MPI_ALLREDUCE( local_2d_l(nxlg,nzb),              &
    1142                                           local_2d(nxlg,nzb), ngp, MPI_REAL, &
     1140                      CALL MPI_ALLREDUCE( local_2d_l(nxlg,nzb),                &
     1141                                          local_2d(nxlg,nzb), ngp, MPI_REAL,   &
    11431142                                          MPI_SUM, comm1dy, ierr )
    11441143#else
     
    11671166!--                   sections reside. Cross sections averaged along y are
    11681167!--                   output on the respective first PE along y (myidy=0).
    1169                       IF ( ( section(is,s) >= nys  .AND.  &
    1170                              section(is,s) <= nyn )  .OR.  &
     1168                      IF ( ( section(is,s) >= nys  .AND.                       &
     1169                             section(is,s) <= nyn )  .OR.                      &
    11711170                           ( section(is,s) == -1  .AND.  myidy == 0 ) )  THEN
    11721171#if defined( __netcdf )
     
    11921191#if defined( __netcdf )
    11931192                         IF ( netcdf_output  .AND.  myid == 0 )  THEN
    1194                             WRITE ( 22 )  time_since_reference_point, &
     1193                            WRITE ( 22 )  time_since_reference_point,          &
    11951194                                          do2d_xz_time_count(av), av
    11961195                         ENDIF
     
    11981197                         DO  i = 0, io_blocks-1
    11991198                            IF ( i == io_group )  THEN
    1200                                IF ( ( section(is,s) >= nys  .AND.   &
    1201                                       section(is,s) <= nyn )  .OR.  &
    1202                                     ( section(is,s) == -1  .AND.    &
    1203                                       nys-1 == -1 ) )               &
     1199                               IF ( ( section(is,s) >= nys  .AND.              &
     1200                                      section(is,s) <= nyn )  .OR.             &
     1201                                    ( section(is,s) == -1  .AND.               &
     1202                                      nys-1 == -1 ) )                          &
    12041203                               THEN
    12051204                                  WRITE (22)  nxlg, nxrg, nzb, nzt+1
     
    12391238!--                            Index limits are received in arbitrary order from
    12401239!--                            the PEs.
    1241                                CALL MPI_RECV( ind(1), 4, MPI_INTEGER,     &
    1242                                               MPI_ANY_SOURCE, 0, comm2d,  &
     1240                               CALL MPI_RECV( ind(1), 4, MPI_INTEGER,          &
     1241                                              MPI_ANY_SOURCE, 0, comm2d,       &
    12431242                                              status, ierr )
    12441243!
     
    12471246                                  sender = status(MPI_SOURCE)
    12481247                                  DEALLOCATE( local_2d )
    1249                                   ALLOCATE( local_2d(ind(1):ind(2), &
     1248                                  ALLOCATE( local_2d(ind(1):ind(2),            &
    12501249                                                     ind(3):ind(4)) )
    12511250                                  CALL MPI_RECV( local_2d(ind(1),ind(3)), ngp, &
    12521251                                                 MPI_REAL, sender, 1, comm2d,  &
    12531252                                                 status, ierr )
    1254                                   total_2d(ind(1):ind(2),ind(3):ind(4)) = &
     1253                                  total_2d(ind(1):ind(2),ind(3):ind(4)) =      &
    12551254                                                                        local_2d
    12561255                               ENDIF
     
    12911290                               ind(3) = -9999; ind(4) = -9999
    12921291                            ENDIF
    1293                             CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0, &
     1292                            CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0,       &
    12941293                                           comm2d, ierr )
    12951294!
    12961295!--                         If applicable, send data to PE0.
    12971296                            IF ( ind(1) /= -9999 )  THEN
    1298                                CALL MPI_SEND( local_2d(nxlg,nzb), ngp, &
     1297                               CALL MPI_SEND( local_2d(nxlg,nzb), ngp,         &
    12991298                                              MPI_REAL, 0, 1, comm2d, ierr )
    13001299                            ENDIF
     
    13351334                      ENDIF
    13361335                      IF ( av == 0 )  THEN
    1337                          rtext = TRIM( do2d(av,if) ) // '  t = ' //    &
    1338                                  TRIM( simulated_time_chr ) // '  ' // &
     1336                         rtext = TRIM( do2d(av,if) ) // '  t = ' //            &
     1337                                 TRIM( simulated_time_chr ) // '  ' //         &
    13391338                                 TRIM( section_chr )
    13401339                      ELSE
    1341                          rtext = TRIM( do2d(av,if) ) // '  averaged t = ' // &
    1342                                  TRIM( simulated_time_chr ) // '  ' //       &
     1340                         rtext = TRIM( do2d(av,if) ) // '  averaged t = ' //   &
     1341                                 TRIM( simulated_time_chr ) // '  ' //         &
    13431342                                 TRIM( section_chr )
    13441343                      ENDIF
     
    13551354                      do2d_yz_last_time(av)  = simulated_time
    13561355                      IF ( myid == 0 )  THEN
    1357                          IF ( ( .NOT. data_output_2d_on_each_pe  .AND.        &
    1358                               netcdf_output )  .OR.  netcdf_data_format > 4 ) &
     1356                         IF ( ( .NOT. data_output_2d_on_each_pe  .AND.         &
     1357                              netcdf_output )  .OR.  netcdf_data_format > 4 )  &
    13591358                         THEN
    13601359#if defined( __netcdf )
     
    13821381                         DO  j = nysg, nyng
    13831382                            DO  i = nxl, nxr
    1384                                local_2d_l(j,k) = local_2d_l(j,k) + &
     1383                               local_2d_l(j,k) = local_2d_l(j,k) +             &
    13851384                                                 local_pf(i,j,k)
    13861385                            ENDDO
     
    13911390!--                   Now do the averaging over all PEs along x
    13921391                      IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    1393                       CALL MPI_ALLREDUCE( local_2d_l(nysg,nzb),              &
    1394                                           local_2d(nysg,nzb), ngp, MPI_REAL, &
     1392                      CALL MPI_ALLREDUCE( local_2d_l(nysg,nzb),                &
     1393                                          local_2d(nysg,nzb), ngp, MPI_REAL,   &
    13951394                                          MPI_SUM, comm1dx, ierr )
    13961395#else
     
    14191418!--                   sections reside. Cross sections averaged along x are
    14201419!--                   output on the respective first PE along x (myidx=0).
    1421                       IF ( ( section(is,s) >= nxl  .AND.  &
    1422                              section(is,s) <= nxr )  .OR.  &
     1420                      IF ( ( section(is,s) >= nxl  .AND.                       &
     1421                             section(is,s) <= nxr )  .OR.                      &
    14231422                           ( section(is,s) == -1  .AND.  myidx == 0 ) )  THEN
    14241423#if defined( __netcdf )
     
    14441443#if defined( __netcdf )
    14451444                         IF ( netcdf_output  .AND.  myid == 0 )  THEN
    1446                             WRITE ( 23 )  time_since_reference_point, &
     1445                            WRITE ( 23 )  time_since_reference_point,          &
    14471446                                          do2d_yz_time_count(av), av
    14481447                         ENDIF
     
    14501449                         DO  i = 0, io_blocks-1
    14511450                            IF ( i == io_group )  THEN
    1452                                IF ( ( section(is,s) >= nxl  .AND.   &
    1453                                       section(is,s) <= nxr )  .OR.  &
    1454                                     ( section(is,s) == -1  .AND.    &
    1455                                       nxl-1 == -1 ) )               &
     1451                               IF ( ( section(is,s) >= nxl  .AND.              &
     1452                                      section(is,s) <= nxr )  .OR.             &
     1453                                    ( section(is,s) == -1  .AND.               &
     1454                                      nxl-1 == -1 ) )                          &
    14561455                               THEN
    14571456                                  WRITE (23)  nysg, nyng, nzb, nzt+1
     
    14911490!--                            Index limits are received in arbitrary order from
    14921491!--                            the PEs.
    1493                                CALL MPI_RECV( ind(1), 4, MPI_INTEGER,     &
    1494                                               MPI_ANY_SOURCE, 0, comm2d,  &
     1492                               CALL MPI_RECV( ind(1), 4, MPI_INTEGER,          &
     1493                                              MPI_ANY_SOURCE, 0, comm2d,       &
    14951494                                              status, ierr )
    14961495!
     
    14991498                                  sender = status(MPI_SOURCE)
    15001499                                  DEALLOCATE( local_2d )
    1501                                   ALLOCATE( local_2d(ind(1):ind(2), &
     1500                                  ALLOCATE( local_2d(ind(1):ind(2),            &
    15021501                                                     ind(3):ind(4)) )
    15031502                                  CALL MPI_RECV( local_2d(ind(1),ind(3)), ngp, &
    15041503                                                 MPI_REAL, sender, 1, comm2d,  &
    15051504                                                 status, ierr )
    1506                                   total_2d(ind(1):ind(2),ind(3):ind(4)) = &
     1505                                  total_2d(ind(1):ind(2),ind(3):ind(4)) =      &
    15071506                                                                        local_2d
    15081507                               ENDIF
     
    15431542                               ind(3) = -9999; ind(4) = -9999
    15441543                            ENDIF
    1545                             CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0, &
     1544                            CALL MPI_SEND( ind(1), 4, MPI_INTEGER, 0, 0,       &
    15461545                                           comm2d, ierr )
    15471546!
    15481547!--                         If applicable, send data to PE0.
    15491548                            IF ( ind(1) /= -9999 )  THEN
    1550                                CALL MPI_SEND( local_2d(nysg,nzb), ngp, &
     1549                               CALL MPI_SEND( local_2d(nysg,nzb), ngp,         &
    15511550                                              MPI_REAL, 0, 1, comm2d, ierr )
    15521551                            ENDIF
     
    15871586                      ENDIF
    15881587                      IF ( av == 0 )  THEN
    1589                          rtext = TRIM( do2d(av,if) ) // '  t = ' //    &
    1590                                  TRIM( simulated_time_chr ) // '  ' // &
     1588                         rtext = TRIM( do2d(av,if) ) // '  t = ' //            &
     1589                                 TRIM( simulated_time_chr ) // '  ' //         &
    15911590                                 TRIM( section_chr )
    15921591                      ELSE
    1593                          rtext = TRIM( do2d(av,if) ) // '  averaged t = ' // &
    1594                                  TRIM( simulated_time_chr ) // '  ' //       &
     1592                         rtext = TRIM( do2d(av,if) ) // '  averaged t = ' //   &
     1593                                 TRIM( simulated_time_chr ) // '  ' //         &
    15951594                                 TRIM( section_chr )
    15961595                      ENDIF
Note: See TracChangeset for help on using the changeset viewer.