Blame test/mpi/f90/topo/cartcrf90.f90

Packit 0848f5
! This file created from test/mpi/f77/topo/cartcrf.f with f77tof90
Packit 0848f5
! -*- Mode: Fortran; -*- 
Packit 0848f5
!
Packit 0848f5
!  (C) 2004 by Argonne National Laboratory.
Packit 0848f5
!      See COPYRIGHT in top-level directory.
Packit 0848f5
!
Packit 0848f5
! Test various combinations of periodic and non-periodic Cartesian 
Packit 0848f5
! communicators
Packit 0848f5
!
Packit 0848f5
      program main
Packit 0848f5
      use mpi
Packit 0848f5
      integer errs, ierr
Packit 0848f5
      integer ndims, nperiods, i, size
Packit 0848f5
      integer comm, source, dest, newcomm
Packit 0848f5
      integer maxdims
Packit 0848f5
      parameter (maxdims=7)
Packit 0848f5
      logical periods(maxdims), outperiods(maxdims)
Packit 0848f5
      integer dims(maxdims), outdims(maxdims)
Packit 0848f5
      integer outcoords(maxdims)
Packit 0848f5
Packit 0848f5
      errs = 0
Packit 0848f5
      call mtest_init( ierr )
Packit 0848f5
Packit 0848f5
!
Packit 0848f5
!     For upto 6 dimensions, test with periodicity in 0 through all
Packit 0848f5
!     dimensions.  The test is computed by both:
Packit 0848f5
!         get info about the created communicator
Packit 0848f5
!         apply cart shift
Packit 0848f5
!     Note that a dimension can have size one, so that these tests
Packit 0848f5
!     can work with small numbers (even 1) of processes
Packit 0848f5
!
Packit 0848f5
      comm = MPI_COMM_WORLD
Packit 0848f5
      call mpi_comm_size( comm, size, ierr )
Packit 0848f5
      do ndims = 1, 6
Packit 0848f5
         do nperiods = 0, ndims
Packit 0848f5
            do i=1,ndims
Packit 0848f5
               periods(i) = .false.
Packit 0848f5
               dims(i)    = 0
Packit 0848f5
            enddo
Packit 0848f5
            do i=1,nperiods
Packit 0848f5
               periods(i) = .true.
Packit 0848f5
            enddo
Packit 0848f5
Packit 0848f5
            call mpi_dims_create( size, ndims, dims, ierr )
Packit 0848f5
            call mpi_cart_create( comm, ndims, dims, periods, .false., &
Packit 0848f5
      &           newcomm, ierr )
Packit 0848f5
Packit 0848f5
            if (newcomm .ne. MPI_COMM_NULL) then
Packit 0848f5
               call mpi_cart_get( newcomm, maxdims, outdims, outperiods, &
Packit 0848f5
      &              outcoords, ierr )
Packit 0848f5
!               print *, 'Coords = '
Packit 0848f5
               do i=1, ndims
Packit 0848f5
!                  print *, i, '(', outcoords(i), ')'
Packit 0848f5
                  if (periods(i) .neqv. outperiods(i)) then
Packit 0848f5
                     errs = errs + 1
Packit 0848f5
                     print *, ' Wrong value for periods ', i
Packit 0848f5
                     print *, ' ndims = ', ndims
Packit 0848f5
                  endif
Packit 0848f5
               enddo
Packit 0848f5
Packit 0848f5
               do i=1, ndims
Packit 0848f5
                  call mpi_cart_shift( newcomm, i-1, 1, source, dest, &
Packit 0848f5
      &                 ierr )
Packit 0848f5
                  if (outcoords(i) .eq. outdims(i)-1) then
Packit 0848f5
                     if (periods(i)) then
Packit 0848f5
                        if (dest .eq. MPI_PROC_NULL) then
Packit 0848f5
                           errs = errs + 1
Packit 0848f5
                           print *, 'Expected rank, got proc_null'
Packit 0848f5
                        endif
Packit 0848f5
                     else
Packit 0848f5
                        if (dest .ne. MPI_PROC_NULL) then
Packit 0848f5
                           errs = errs + 1
Packit 0848f5
                           print *, 'Expected procnull, got ', dest
Packit 0848f5
                        endif
Packit 0848f5
                     endif
Packit 0848f5
                  endif
Packit 0848f5
                  
Packit 0848f5
                  call mpi_cart_shift( newcomm, i-1, -1, source, dest, &
Packit 0848f5
      &                 ierr )
Packit 0848f5
                  if (outcoords(i) .eq. 0) then
Packit 0848f5
                     if (periods(i)) then
Packit 0848f5
                        if (dest .eq. MPI_PROC_NULL) then
Packit 0848f5
                           errs = errs + 1
Packit 0848f5
                           print *, 'Expected rank, got proc_null'
Packit 0848f5
                        endif
Packit 0848f5
                     else
Packit 0848f5
                        if (dest .ne. MPI_PROC_NULL) then
Packit 0848f5
                           errs = errs + 1
Packit 0848f5
                           print *, 'Expected procnull, got ', dest
Packit 0848f5
                        endif
Packit 0848f5
                     endif
Packit 0848f5
                  endif
Packit 0848f5
               enddo
Packit 0848f5
               call mpi_comm_free( newcomm, ierr )
Packit 0848f5
            endif
Packit 0848f5
            
Packit 0848f5
         enddo
Packit 0848f5
      enddo
Packit 0848f5
      
Packit 0848f5
      call mtest_finalize( errs )
Packit 0848f5
      call mpi_finalize( ierr )
Packit 0848f5
      end