Ignore:
Timestamp:
Oct 18, 2018 2:03:19 PM (6 years ago)
Author:
raasch
Message:

bugfix: kind type of 2nd argument of mpi_win_allocate changed, misplaced parallel directive

File:
1 edited

Legend:

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

    r3351 r3372  
    2828! -----------------
    2929! $Id$
     30! bugfix: kind type of 2nd argument of mpi_win_allocate changed, misplaced
     31!         __parallel directive
     32!
     33! 3351 2018-10-15 18:40:42Z suehring
    3034! Do not overwrite values of spectral and broadband albedo during initialization
    3135! if they are already initialized in the urban-surface model via ASCII input.
     
    56635667
    56645668          CALL MPI_Win_allocate(INT(STORAGE_SIZE(1_iwp)/8*nsurf_type_u*nzu*nny*nnx, &
    5665                                     kind=MPI_ADDRESS_KIND),                         &
    5666                                 INT(STORAGE_SIZE(1_iwp)/8, kind=MPI_ADDRESS_KIND),  &
     5669                                    kind=MPI_ADDRESS_KIND), STORAGE_SIZE(1_iwp)/8,  &
    56675670                                minfo, comm2d, gridsurf_rma_p, win_gridsurf, ierr)
    56685671          IF ( ierr /= 0 ) THEN
    56695672              WRITE(9,*) 'Error MPI_Win_allocate1:', ierr, &
    56705673                 INT(STORAGE_SIZE(1_iwp)/8*nsurf_type_u*nzu*nny*nnx,kind=MPI_ADDRESS_KIND), &
    5671                  INT(STORAGE_SIZE(1_iwp)/8, kind=MPI_ADDRESS_KIND), win_gridsurf
     5674                 STORAGE_SIZE(1_iwp)/8, win_gridsurf
    56725675              FLUSH(9)
    56735676          ENDIF
     
    76177620
    76187621   CONTAINS
    7619       SUBROUTINE request_itarget(d, z, y, x, isurfl, iproc)
     7622
     7623      SUBROUTINE request_itarget( d, z, y, x, isurfl, iproc )
     7624
    76207625         INTEGER(iwp), INTENT(in)            ::  d, z, y, x
    76217626         INTEGER(iwp), TARGET, INTENT(out)   ::  isurfl
    76227627         INTEGER(iwp), INTENT(out)           ::  iproc
    7623          INTEGER(kind=MPI_ADDRESS_KIND)      ::  target_displ  !< index of the grid in the local gridsurf array
    76247628         INTEGER(iwp)                        ::  px, py        !< number of processors in x and y direction
    76257629                                                               !< before the processor in the question
    7626 
    7627 !--      calculate target processor and index in the remote local target gridsurf array
    7628          px = x/nnx
    7629          py = y/nny
    7630          iproc = px*pdims(2)+py
    7631          target_displ = ((x-px*nnx)*nny + y-py*nny)*nzu*nsurf_type_u + (z-nzub)*nsurf_type_u + d
    7632 
    76337630#if defined( __parallel )
    7634 !--      send MPI_Get request to obtain index target_surfl(i)
    7635          CALL MPI_Get(isurfl, 1, MPI_INTEGER, iproc, target_displ, &
    7636                         1, MPI_INTEGER, win_gridsurf, ierr)
     7631         INTEGER(KIND=MPI_ADDRESS_KIND)      ::  target_displ  !< index of the grid in the local gridsurf array
     7632
     7633!
     7634!--      Calculate target processor and index in the remote local target gridsurf array
     7635         px = x / nnx
     7636         py = y / nny
     7637         iproc = px * pdims(2) + py
     7638         target_displ = ((x-px*nnx) * nny + y - py*nny ) * nzu * nsurf_type_u +&
     7639                        ( z-nzub ) * nsurf_type_u + d
     7640!
     7641!--      Send MPI_Get request to obtain index target_surfl(i)
     7642         CALL MPI_GET( isurfl, 1, MPI_INTEGER, iproc, target_displ,            &
     7643                       1, MPI_INTEGER, win_gridsurf, ierr)
    76377644         IF ( ierr /= 0 )  THEN
    7638             WRITE(9,*) 'Error MPI_Get3:', ierr, isurfl, iproc, target_displ, win_gridsurf
    7639             FLUSH(9)
     7645            WRITE( 9,* ) 'Error MPI_Get3:', ierr, isurfl, iproc, target_displ, &
     7646                         win_gridsurf
     7647            FLUSH( 9 )
    76407648         ENDIF
    76417649#else
     
    76437651         isurfl = gridsurf(d,z,y,x)
    76447652#endif
     7653
    76457654      END SUBROUTINE request_itarget
    76467655
Note: See TracChangeset for help on using the changeset viewer.