MFIX  2016-1
check_dmp_prereqs.f
Go to the documentation of this file.
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 required.
45  INTEGER, PARAMETER :: DMP_MIN = 3
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  ' Domain decomposition : ',i8,/)
142 
143 
144  END SUBROUTINE check_dmp_prereqs
subroutine finl_err_msg
subroutine check_dmp_prereqs
integer numpes
Definition: compar_mod.f:24
integer imax
Definition: geometry_mod.f:47
subroutine init_err_msg(CALLER)
integer kmax
Definition: geometry_mod.f:51
integer nodesj
Definition: compar_mod.f:37
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
integer nodesk
Definition: compar_mod.f:37
integer jmax
Definition: geometry_mod.f:49
integer nodesi
Definition: compar_mod.f:37
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)