File: mp_pots.f90

package info (click to toggle)
espresso 5.1%2Bdfsg-3
  • links: PTS, VCS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 146,004 kB
  • ctags: 17,245
  • sloc: f90: 253,041; sh: 51,271; ansic: 27,494; tcl: 15,570; xml: 14,508; makefile: 2,958; perl: 2,035; fortran: 1,924; python: 337; cpp: 200; awk: 57
file content (90 lines) | stat: -rw-r--r-- 3,080 bytes parent folder | download
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
!
! Copyright (C) 2013 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 .
!
!----------------------------------------------------------------------------
MODULE mp_pots
  !----------------------------------------------------------------------------
  !
  USE mp, ONLY : mp_barrier, mp_size, mp_rank, mp_comm_split
  USE parallel_include
  !
  IMPLICIT NONE 
  SAVE
  !
  ! ... Pot groups (processors within a cooking-pot)
  ! ... Used only in a specialized calculation under development 
  !
  INTEGER :: npot       = 1  ! number of pots
  INTEGER :: nproc_pot  = 1  ! number of processors within a pot
  INTEGER :: me_pot     = 0  ! index of the processor within a pot
  INTEGER :: root_pot   = 0  ! index of the root processor within a pot
  INTEGER :: my_pot_id  = 0  ! index of my pot
  INTEGER :: inter_pot_comm  = 0  ! inter pot communicator
  INTEGER :: intra_pot_comm  = 0  ! intra pot communicator
  !
CONTAINS
  !
  !----------------------------------------------------------------------------
  SUBROUTINE mp_start_pots ( npot_, parent_comm )
    !---------------------------------------------------------------------------
    !
    ! ... Divide processors (of the "parent_comm" group) into "pots"
    ! ... Requires: npot_, read from command line
    ! ...           parent_comm, typically processors of an "image"
    ! ...           (intra_image_comm)
    !
    IMPLICIT NONE
    !
    INTEGER, INTENT(IN) :: npot_, parent_comm
    !
    INTEGER :: parent_nproc = 1, parent_mype  = 0
    !
#if defined (__MPI)
    !
    parent_nproc = mp_size( parent_comm )
    parent_mype  = mp_rank( parent_comm )
    !
    ! ... npot_ must have been previously read from command line argument
    ! ... by a call to routine get_command_line
    !
    npot = npot_
    !
    IF ( npot < 1 .OR. npot > parent_nproc ) CALL errore( 'mp_start_pots',&
                          'invalid number of pot groups, out of range', 1 )

    IF ( MOD( parent_nproc, npot ) /= 0 ) CALL errore( 'mp_start_pots', &
           'invalid number of pots, parent_nproc /= nproc_pot * npot', 1 )  
    !
    ! ... number of cpus per pot (they are created inside each parent group)
    !
    nproc_pot = parent_nproc / npot
    !
    !
    ! ... my_pot_id  =  pot index for this processor    ( 0 : npot - 1 )
    ! ... me_pot     =  processor index within the pot  ( 0 : nproc_pot - 1 )
    !
    my_pot_id = parent_mype / nproc_pot    
    me_pot    = MOD( parent_mype, nproc_pot )
    !
    CALL mp_barrier( parent_comm )
    !
    ! ... the intra_pot_comm communicator is created
    !
    CALL mp_comm_split( parent_comm, my_pot_id, parent_mype, intra_pot_comm )
    !
    CALL mp_barrier( parent_comm )
    !
    ! ... the inter_pot_comm communicator is created
    !
    CALL mp_comm_split( parent_comm, me_pot, parent_mype, inter_pot_comm )
    !
#endif
    !
    RETURN
  END SUBROUTINE mp_start_pots
  !
END MODULE mp_pots