subroutine RearrangeColumn( xya_Data )
    !
    ! Rearrange columns
    !
    ! MPI
    !
    use mpi_wrapper, only: nprocs, myrank, MPIWrapperISend, MPIWrapperIRecv, MPIWrapperWait
    real(DP), intent(inout) :: xya_Data(:,:,:)
    ! 作業変数
    ! Work variables
    !
    real(DP), allocatable :: xyaa_SendBuf(:,:,:,:)
    real(DP), allocatable :: xyaa_RecvBuf(:,:,:,:)
    integer :: imaxLocal
    integer :: jmaxLocal
    integer :: kmaxLocal
    integer :: imaxBlock
    integer :: iLocal
    integer :: a_iReqSend(0:nprocs-1)
    integer :: a_iReqRecv(0:nprocs-1)
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitudinal direction
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitudinal direction
    integer:: n
    ! 実行文 ; Executable statement
    !
    imaxLocal = size( xya_Data, 1 )
    jmaxLocal = size( xya_Data, 2 )
    kmaxLocal = size( xya_Data, 3 )
    if ( mod( imaxLocal/2, nprocs ) /= 0 ) then
      call MessageNotify( 'E', module_name, 'nprocs value is inappropriate, nprocs = %d', i = (/ nprocs /) )
    end if
    if ( mod( imaxLocal/2/nprocs, 2 ) /= 0 ) then
      call MessageNotify( 'E', module_name, 'nprocs value is inappropriate, nprocs = %d', i = (/ nprocs /) )
    end if
    imaxBlock = imaxLocal / nprocs
    allocate( xyaa_SendBuf(1:imaxBlock,1:jmaxLocal,1:kmaxLocal,0:nprocs-1) )
    allocate( xyaa_RecvBuf(1:imaxBlock,1:jmaxLocal,1:kmaxLocal,0:nprocs-1) )
    ! pack data transfered to nth process
    do n = 0, nprocs-1
      iLocal = 1
      do i = n+1, imaxLocal, nprocs
        xyaa_SendBuf(iLocal,:,:,n) = xya_Data(i,:,:)
        iLocal = iLocal + 1
      end do
    end do
    do n = 0, nprocs-1
      xyaa_RecvBuf = xyaa_SendBuf
    end do
    do n = 0, nprocs-1
      if ( n == myrank ) then
        xyaa_RecvBuf(:,:,:,n) = xyaa_SendBuf(:,:,:,n)
      else
        call MPIWrapperISend( n, imaxBlock, jmaxLocal, kmaxLocal, xyaa_SendBuf(:,:,:,n), a_iReqSend(n) )
        call MPIWrapperIRecv( n, imaxBlock, jmaxLocal, kmaxLocal, xyaa_RecvBuf(:,:,:,n), a_iReqRecv(n) )
      end if
    end do
    do n = 0, nprocs-1
      if ( n == myrank ) cycle
      call MPIWrapperWait( a_iReqSend(n) )
      call MPIWrapperWait( a_iReqRecv(n) )
    end do
    ! pack data transfered to nth process
    do n = 0, nprocs-1
      iLocal = 1
      do i = n+1, imaxLocal, nprocs
        xya_Data(i,:,:) = xyaa_RecvBuf(iLocal,:,:,n)
        iLocal = iLocal + 1
      end do
    end do
    deallocate( xyaa_SendBuf )
    deallocate( xyaa_RecvBuf )
  end subroutine RearrangeColumn