generate_2D_hammersley_sequence Subroutine

public subroutine generate_2D_hammersley_sequence(ID, NMPIS, X, Y)

@brief Subroutine for generating a 2-D Hammersley sequence. @details This subroutine uses the algorithm for generating a 1-D Hammersley sequence. Each MPI process in KORC generates a (different) subset of pairs (X,Y) of a 2-D Hammersley sequence. The total number of pairs (X,Y) is NMPIS*N, where NMPIS is the number of MPI processes in the simulation and N is the number of particles followed by each MPI process. Each subset of pairs (X,Y) has N elements.

@param[in,out] X 1-D array with elements of a 2-D Hammersley sequence. @param[in,out] Y 1-D array with elements of a 2-D Hammersley sequence. @param[in] ID MPI rank of MPI process. @param[in] NMPIS Total number of MPI processes in the simulation. @param N Number of particles per MPI process. @param offset An offset to indicate the subroutine what subset of the 2-D Harmmersley sequence will be generated. @param ii Particle iterator.

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: ID
integer, intent(in) :: NMPIS
real(kind=rp), intent(inout), DIMENSION(:):: X
real(kind=rp), intent(inout), DIMENSION(:):: Y

Contents


Source Code

  subroutine generate_2D_hammersley_sequence(ID,NMPIS,X,Y)
    REAL(rp), DIMENSION(:), INTENT(INOUT) 	:: X
    REAL(rp), DIMENSION(:), INTENT(INOUT) 	:: Y
    INTEGER, INTENT(IN) 					:: ID
    INTEGER, INTENT(IN) 					:: NMPIS
    INTEGER(4) 								:: N
    INTEGER(4) 								:: offset
    REAL(8), DIMENSION(2) 					:: R
    INTEGER(4) 								:: ii

    N = INT(SIZE(X),4)
    offset = (INT(ID+1_idef,4) - 1_4)*N

    !	write(output_unit_write,'("MPI process: ",I5," offset: ",I5)') ID, offset

    do ii=1_4,N
       call hammersley(ii+INT(offset,4),2_4,N*INT(NMPIS,4),R)

       X(ii) = REAL(R(1),rp)
       Y(ii) = REAL(R(2),rp)
    end do
  end subroutine generate_2D_hammersley_sequence