File: divide.f90

package info (click to toggle)
espresso 6.7-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 311,068 kB
  • sloc: f90: 447,429; ansic: 52,566; sh: 40,631; xml: 37,561; tcl: 20,077; lisp: 5,923; makefile: 4,503; python: 4,379; perl: 1,219; cpp: 761; fortran: 618; java: 568; awk: 128
file content (106 lines) | stat: -rw-r--r-- 3,150 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
!
! Copyright (C) 2012 Quantum ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
!
!-----------------------------------------------------------------------
SUBROUTINE divide (comm, ntodiv, startn, lastn)
  !-----------------------------------------------------------------------
  !
  ! Given "ntodiv" objects, distribute index across a group of processors
  ! belonging to communicator "comm"
  ! Each processor gets index from "startn" to "lastn"
  ! If the number of processors nproc exceeds the number of objects,
  ! the last nproc-ntodiv processors return startn = ntodiv+1 > lastn = ntodiv
  !
  USE mp, ONLY : mp_size, mp_rank
  IMPLICIT NONE
  !
  INTEGER, INTENT(in) :: comm
  ! communicator
  INTEGER, INTENT(in) :: ntodiv
  ! index to be distributed
  INTEGER, INTENT(out):: startn, lastn
  ! indices for this processor: from startn to lastn
  !
  INTEGER :: me_comm, nproc_comm
  ! identifier of current processor
  ! number of processors
  !
  INTEGER :: ndiv, rest
  ! number of points per processor
  ! number of processors having one more points
  !
  nproc_comm = mp_size(comm)
  me_comm = mp_rank(comm)
  !
  rest = mod ( ntodiv, nproc_comm )
  ndiv = int( ntodiv / nproc_comm ) 
  !
  IF (rest > me_comm) THEN 
     startn =  me_comm    * (ndiv+1) + 1
     lastn  = (me_comm+1) * (ndiv+1) 
  ELSE
     startn=  me_comm    * ndiv + rest + 1
     lastn = (me_comm+1) * ndiv + rest 
  ENDIF

  RETURN

END SUBROUTINE divide

SUBROUTINE divide_all (comm, ntodiv, startn, lastn, counts, displs)
  !-----------------------------------------------------------------------
  !
  ! Given "ntodiv" objects, distribute index across a group of processors
  ! belonging to communicator "comm"
  ! Each processor gets index from "startn" to "lastn"
  ! If the number of processors nproc exceeds the number of objects,
  ! the last nproc-ntodiv processors return startn = ntodiv+1 > lastn = ntodiv
  !
  USE mp, ONLY : mp_size, mp_rank
  IMPLICIT NONE
  !
  INTEGER, INTENT(in) :: comm
  ! communicator
  INTEGER, INTENT(in) :: ntodiv
  ! index to be distributed
  INTEGER, INTENT(out):: startn, lastn
  ! indices for this processor: from startn to lastn
  INTEGER, INTENT(out):: counts(*), displs(*)
  ! indice counts and displacements of all ranks
  !
  INTEGER :: me_comm, nproc_comm
  ! identifier of current processor
  ! number of processors
  !
  INTEGER :: ndiv, rest
  ! number of points per processor
  ! number of processors having one more points
  INTEGER :: ip
  !
  nproc_comm = mp_size(comm)
  me_comm = mp_rank(comm)
  !
  rest = mod ( ntodiv, nproc_comm )
  ndiv = int( ntodiv / nproc_comm )
  !
  DO ip = 1, nproc_comm
     IF (rest >= ip) THEN
        counts(ip) = ndiv + 1
        displs(ip)  = (ip-1) * (ndiv+1)
     ELSE
        counts(ip) = ndiv
        displs(ip)  = (ip-1) * ndiv + rest
     ENDIF
  ENDDO
  ! seting startn and lastn
  startn =  displs(me_comm+1) + 1
  lastn = displs(me_comm+1) + counts(me_comm+1)

  RETURN

END SUBROUTINE divide_all