Ignore:
Timestamp:
Sep 7, 2010 2:50:07 PM (14 years ago)
Author:
weinreis
Message:

bugfix message string in set_mask_locations

File:
1 edited

Legend:

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

    r494 r557  
    7777    CHARACTER (LEN=50) ::  rtext
    7878    INTEGER ::  av, ngp, file_id, i, if, is, iis, j, k, l, layer_xy, n, psi, &
    79                 s, sender, &
     79                rbs, s, sender, &
    8080                ind(4)
    8181    LOGICAL ::  found, resorted, two_d
     
    720720                         ENDIF
    721721#endif
    722                          WRITE ( 21 )  nxl-1, nxr+1, nys-1, nyn+1
    723                          WRITE ( 21 )  local_2d
    724 
     722                         DO rbs = 0, numprocs/binary_io_blocksize-1       
     723                            IF ( mod_numprocs_size == rbs ) THEN
     724                               WRITE ( 21 )  nxl-1, nxr+1, nys-1, nyn+1
     725                               WRITE ( 21 )  local_2d
     726                            ENDIF     
     727                            CALL MPI_BARRIER(comm2d, ierr )
     728                         ENDDO
     729                     
    725730                      ELSE
    726731!
     
    10131018                         ENDIF
    10141019#endif
    1015                          IF ( ( section(is,s) >= nys  .AND.                  &
    1016                                 section(is,s) <= nyn )  .OR.                 &
    1017                               ( section(is,s) == -1  .AND.  nys-1 == -1 ) )  &
    1018                          THEN
    1019                             WRITE (22)  nxl-1, nxr+1, nzb, nzt+1
    1020                             WRITE (22)  local_2d
    1021                          ELSE
    1022                             WRITE (22)  -1, -1, -1, -1
    1023                          ENDIF
     1020                         DO rbs = 0, numprocs/binary_io_blocksize-1       
     1021                            IF ( mod_numprocs_size == rbs ) THEN
     1022                               IF ( ( section(is,s) >= nys  .AND.            &
     1023                                      section(is,s) <= nyn )  .OR.           &
     1024                                    ( section(is,s) == -1  .AND.             &
     1025                                      nys-1 == -1 ) )                        &
     1026                               THEN
     1027                                  WRITE (22)  nxl-1, nxr+1, nzb, nzt+1
     1028                                  WRITE (22)  local_2d
     1029                               ELSE
     1030                                  WRITE (22)  -1, -1, -1, -1
     1031                               ENDIF
     1032                            ENDIF     
     1033                            CALL MPI_BARRIER(comm2d, ierr )
     1034                         ENDDO
    10241035
    10251036                      ELSE
     
    13121323                         ENDIF
    13131324#endif
    1314                          IF ( ( section(is,s) >= nxl  .AND.                  &
    1315                                 section(is,s) <= nxr )  .OR.                 &
    1316                               ( section(is,s) == -1  .AND.  nxl-1 == -1 ) )  &
    1317                          THEN
    1318                             WRITE (23)  nys-1, nyn+1, nzb, nzt+1
    1319                             WRITE (23)  local_2d
    1320                          ELSE
    1321                             WRITE (23)  -1, -1, -1, -1
    1322                          ENDIF
     1325                         DO rbs = 0, numprocs/binary_io_blocksize-1       
     1326                            IF ( mod_numprocs_size == rbs ) THEN
     1327                               IF ( ( section(is,s) >= nxl  .AND.            &
     1328                                      section(is,s) <= nxr )  .OR.           &
     1329                                    ( section(is,s) == -1  .AND.             &
     1330                                      nxl-1 == -1 ) )                        &
     1331                               THEN
     1332                                  WRITE (23)  nys-1, nyn+1, nzb, nzt+1
     1333                                  WRITE (23)  local_2d
     1334                               ELSE
     1335                                  WRITE (23)  -1, -1, -1, -1
     1336                               ENDIF
     1337                            ENDIF     
     1338                            CALL MPI_BARRIER(comm2d, ierr )
     1339                         ENDDO
    13231340
    13241341                      ELSE
Note: See TracChangeset for help on using the changeset viewer.