reimage_distribution Subroutine

private subroutine reimage_distribution(images, my_bins, nbins, nimages)

Makes new distribution with decimation and multiplicity Multiplicity is being ignored, maybe this is a bug

Definition of multiplicity and nimages Multiplicity and decimation (number of images) are used to match process grid coordinates on non-square process grids. Given source_nbins and target_nbins, their relation is source_nbins * target_multiplicity = target_nbins * target_nimages. It is best when both multiplicity and nimages are small. To get these two factors, then, one can use the following formulas: nimages = lcm(source_nbins, target_nbins) / target_nbins multiplicity = target_nbins / gcd(source_nbins, target_nbins) from the target's point of view (nimages = target_nimages).

Mapping The new distribution comprises of real bins and images within bins. These can be view as target_nbinsnimages virtual columns. These same virtual columns are also source_nbinsmultiplicity in number. Therefore these virtual columns are mapped from source_nbinsmultiplicity onto target_binsnimages (each target bin has nimages images): Source 4: |1 2 3|4 5 6|7 8 9|A B C| (43) Target 6: |1 2|3 4|5 6|7 8|9 A|B C| (62) multiplicity=3, nimages=2, 12 virtual columns (1-C). Source bin elements are evenly mapped into one of multiplicity virtual columns. Other (non-even, block-size aware) mappings could be better.

Arguments

Type IntentOptional Attributes Name
integer, intent(out), DIMENSION(:) :: images

new image distribution

integer, intent(in), DIMENSION(:) :: my_bins

Basis for the new images

integer, intent(in) :: nbins

number of bins in the new real distribution number of images in the new distribution

integer, intent(in) :: nimages

number of bins in the new real distribution number of images in the new distribution


Source Code

   SUBROUTINE reimage_distribution(images, my_bins, &
                                   nbins, nimages)
      !! Makes new distribution with decimation and multiplicity
      !! Multiplicity is being ignored, maybe this is a bug
      !!
      !! Definition of multiplicity and nimages
      !! Multiplicity and decimation (number of images) are used to
      !! match process grid coordinates on non-square process
      !! grids. Given source_nbins and target_nbins, their relation is
      !! source_nbins * target_multiplicity
      !! = target_nbins * target_nimages.
      !! It is best when both multiplicity and nimages are small. To
      !! get these two factors, then, one can use the following formulas:
      !! nimages      = lcm(source_nbins, target_nbins) / target_nbins
      !! multiplicity = target_nbins / gcd(source_nbins, target_nbins)
      !! from the target's point of view (nimages = target_nimages).
      !!
      !! Mapping
      !! The new distribution comprises of real bins and images within
      !! bins. These can be view as target_nbins*nimages virtual
      !! columns. These same virtual columns are also
      !! source_nbins*multiplicity in number. Therefore these virtual
      !! columns are mapped from source_nbins*multiplicity onto
      !! target_bins*nimages (each target bin has nimages images):
      !! Source 4: |1 2 3|4 5 6|7 8 9|A B C| (4*3)
      !! Target 6: |1 2|3 4|5 6|7 8|9 A|B C| (6*2)
      !! multiplicity=3, nimages=2, 12 virtual columns (1-C).
      !! Source bin elements are evenly mapped into one of multiplicity
      !! virtual columns. Other (non-even, block-size aware) mappings
      !! could be better.

      INTEGER, DIMENSION(:), INTENT(OUT)                 :: images
         !! new image distribution
      INTEGER, DIMENSION(:), INTENT(IN)                  :: my_bins
         !! Basis for the new images
      INTEGER, INTENT(IN)                                :: nbins, nimages
         !! number of bins in the new real distribution
         !! number of images in the new distribution

      INTEGER                                            :: bin, i
      INTEGER, ALLOCATABLE, DIMENSION(:)                 :: bin_multiplier

!   ---------------------------------------------------------------------------

      ALLOCATE (bin_multiplier(0:nbins - 1))
      bin_multiplier(:) = 0
      DO i = 1, SIZE(my_bins)
         bin = my_bins(i)
         images(i) = 1 + bin_multiplier(bin)
         bin_multiplier(bin) = bin_multiplier(bin) + 1
         IF (bin_multiplier(bin) .GE. nimages) THEN
            bin_multiplier(bin) = 0
         END IF
      END DO
   END SUBROUTINE reimage_distribution