UPP  11.0.0
 All Data Structures Files Functions Variables Pages
PARA_RANGE.f
Go to the documentation of this file.
1 
19 !-----------------------------------------------------------------
29  SUBROUTINE para_range (N1,N2,NPROCS,IRANK,ISTA,IEND)
30 
31  implicit none
32  integer,intent(in) :: n1,n2,nprocs,irank
33  integer,intent(out) :: ista,iend
34  integer iwork1, iwork2
35 
36  iwork1 = ( n2 - n1 + 1 ) / nprocs
37  iwork2 = mod( n2 - n1 + 1, nprocs )
38  ista = irank * iwork1 + n1 + min( irank, iwork2 )
39  iend = ista + iwork1 - 1
40  if ( iwork2 > irank ) iend = iend + 1
41  return
42  end
43 !!
44 !! USAGE: CALL PARA_RANGE2(N1,N2,NX,NY,NRANK,ISTA,IEND,JSTA,JEND)(A)
45 !! INPUT ARGUMENT LIST:
46 !! N1 - LAAT INTERATE VALUE I dimension
47 !! N2 - LAST INTERATE VALUE J dimension
48 !! NX NUMBER OF subdomains in Z dimension
49 !! NY NUMBER OF subdomains in Y dimension
50 !! NX * NY should be the total number of MPI procs
51 !! NRANK - MY TAKS ID
52 !!
53 !! OUTPUT ARGUMENT LIST:
54 !! ISTA - FIRST LOOP VALUE I
55 !! IEND - LAST LOOP VALUE I
56 !! JSTA - FIRST LOOP VALUE J
57 !! JEND - LAST LOOP VALUE J
58 !!
59 !! OUTPUT FILES:
60 !! STDOUT - RUN TIME STANDARD OUT.
61 !!
62 !! SUBPROGRAMS CALLED:
63 !! UTILITIES:
64 !! NONE
65 !! LIBRARY:
66 !!
67 !! ATTRIBUTES:
68 !! LANGUAGE: FORTRAN
69 !! MACHINE : IBM RS/6000 SP
70 !!
71  subroutine para_range2(im,jm,nx,ny,nrank,ista,iend,jsta,jend)
72 
73  implicit none
74  integer,intent(in) :: im,jm,nx,ny,nrank
75  integer,intent(out) :: ista,iend,jsta,jend
76  integer :: ix,jx
77 
78  jx=nrank/nx
79  ix=nrank-(jx*nx)
80  call para_range(1,im,nx,ix,ista,iend)
81  call para_range(1,jm,ny,jx,jsta,jend)
82 ! print 101,n,ix,jx,ista,iend,jsta,jend
83 ! 101 format(16i8)
84  return
85  end
86 
87 
subroutine para_range(N1, N2, NPROCS, IRANK, ISTA, IEND)
para_range() sets up decomposition values.
Definition: PARA_RANGE.f:29