File: /nfs/home/0/users/jenkins/mfix.git/model/check_data/check_dmp_prereqs.f

1     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2     !                                                                      !
3     !  SUBROUTINE: CHECK_DMP_PREREQS                                       !
4     !  Purpose: Check the distributed parallel namelist variables.         !
5     !                                                                      !
6     !  Author: P. Nicoletti                               Date: 14-DEC-99  !
7     !  Reviewer: J.Musser                                 Date: 16-Jan-14  !
8     !                                                                      !
9     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
10           SUBROUTINE CHECK_DMP_PREREQS
11     
12     
13     ! Global Variables:
14     !---------------------------------------------------------------------//
15     ! Number of ranks.
16           use compar, only: numPEs
17     ! DMP grid partitioning data:
18           use compar, only: NODESI  ! Partitions along x-axis
19           use compar, only: NODESJ  ! Partitions along y-axis
20           use compar, only: NODESK  ! Partitions along z-axis
21     ! Domain partitions in various directions.
22           use geometry, only: IMAX
23           use geometry, only: JMAX
24           use geometry, only: KMAX
25     
26     ! Global Parameters:
27     !---------------------------------------------------------------------//
28           use param1, only: UNDEFINED_I
29     
30     ! Use the error manager for posting error messages.
31     !---------------------------------------------------------------------//
32           use error_manager
33     
34           implicit none
35     
36     ! Local Variables:
37     !---------------------------------------------------------------------//
38     ! The approximate number of domain partitions that will be assigned
39     ! to each process for DMP runs. (eg IMAX/NODESI)
40           INTEGER :: LAYERS
41     
42     ! Local Parameters:
43     !---------------------------------------------------------------------//
44     ! The minimum number of computational cell layers requried.
45           INTEGER, PARAMETER :: DMP_MIN = 4
46     
47     ! Initialize the error manager.
48           CALL INIT_ERR_MSG("CHECK_DMP_PREREQS")
49     
50     ! Verify that DMP partitioning information is provided given if
51     ! there is more than one rank.
52           IF( numPEs > 1 ) then
53              IF(NODESI .EQ. UNDEFINED_I .AND.                              &
54                 NODESJ .EQ. UNDEFINED_I .AND.                              &
55                 NODESK .EQ. UNDEFINED_I) THEN
56                 WRITE(ERR_MSG,1000)
57                 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
58              ENDIF
59           ENDIF
60     
61     ! Initialize NODE values if undefined. If this is a DMP run, then a
62     ! warning message is passed to the user.
63           IF (NODESI .EQ. UNDEFINED_I) THEN
64              IF(numPEs > 1) THEN
65                 WRITE(ERR_MSG,1001)'I','I'
66                 CALL FLUSH_ERR_MSG
67              ENDIF
68              NODESI = 1
69     ! Verify that the DMP partition is appropriate for the domain.
70           ELSEIF(NODESI > 1) THEN
71              LAYERS=int(IMAX/NODESI)
72              IF(LAYERS < DMP_MIN) THEN
73                 WRITE(ERR_MSG,1002) 'X', DMP_MIN, 'I', 'I', LAYERS
74                 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
75              ENDIF
76           ENDIF
77     
78           IF (NODESJ .EQ. UNDEFINED_I) THEN
79              IF(numPEs > 1) THEN
80                 WRITE(ERR_MSG,1001)'J','J'
81                 CALL FLUSH_ERR_MSG
82              ENDIF
83              NODESJ = 1
84     
85     ! Verify that the DMP partition is appropriate for the domain.
86           ELSEIF(NODESJ > 1) THEN
87              LAYERS=int(JMAX/NODESJ)
88              IF(LAYERS < DMP_MIN) THEN
89                 WRITE(ERR_MSG,1002) 'Y', DMP_MIN, 'J', 'J', LAYERS
90                 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
91              ENDIF
92           ENDIF
93     
94           IF (NODESK .EQ. UNDEFINED_I) THEN
95              IF(numPEs > 1) THEN
96                 WRITE(ERR_MSG,1001)'K','K'
97                 CALL FLUSH_ERR_MSG
98              ENDIF
99              NODESK = 1
100     ! Verify that the DMP partition is appropriate for the domain.
101           ELSEIF(NODESK > 1) THEN
102              LAYERS=int(KMAX/NODESK)
103              IF(LAYERS < DMP_MIN) THEN
104                 WRITE(ERR_MSG,1002) 'Z', DMP_MIN, 'K', 'K', LAYERS
105                 CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
106              ENDIF
107           ENDIF
108     
109     ! Verify that the number of requested processes (munPEs) matches
110     ! the domain decomposition (nodesi * nodesj * nodesk).
111           IF(numPEs .NE. (NODESi*NODESj*NODESk)) THEN
112              WRITE(ERR_MSG,1003) numPEs, (NODESi*NODESj*NODESk)
113              CALL FLUSH_ERR_MSG(ABORT=.TRUE.)
114           ENDIF
115     
116     
117           CALL FINL_ERR_MSG
118     
119           RETURN
120     
121     
122      1000 FORMAT('Error 1000: No DMP grid partitioning data provided in ', &
123              'mfix.dat.',/'NODESI, NODESJ, and NODESK are all undefined.',/&
124              'Refer to the users manual for required input and make the ', &
125              'necessary',/'corrections to the input data file.')
126     
127      1001 FORMAT('Warning 1001: Setting NODES',A1,' to default: ',         &
128              'NODES',A1,'=1.')
129     
130      1002 FORMAT('Error 1002:  Too many DMP partitions specified for ',    &
131              A1,' axis.',/'There must be at least ',I2,' computational ',  &
132              'cells per DMP parition.',/' >>> Computational Cells/DMP ',   &
133              'Partition = int(',A1,'MAX/NODES',A1,') = ',I2,/'Refer to ',  &
134              'the users manual for required input and make the necessary',/&
135              'corrections to the input data file.')
136     
137      1003 FORMAT('Error 1003: The number of requested processors is ',     &
138              'inconsistent',/'with the domain decomposition, (NODESi * ',  &
139              'NODESj * NODESk).',/' These numbers must match.',2/,         &
140              '  Number of requested processes: ',I8,/,                     &
141              '  Doman decomposition : ',I8,/)
142     
143     
144           END SUBROUTINE CHECK_DMP_PREREQS
145