MFIX  2016-1
check_geometry_prereqs.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! SUBROUTINE: CHECK_GEOMETRY_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_geometry_prereqs
11 
12 
13 
14 ! Global Variables:
15 !---------------------------------------------------------------------//
16 ! Domain partitions in various directions.
17  use geometry, only: imax, no_i, xmin
18  use geometry, only: jmax, no_j
19  use geometry, only: kmax, no_k, dz, zlength
20 
21 ! Runtime flag specifying 2D simulations
22 ! use geometry, only: NO_K
23 
24  use geometry, only: coordinates, cylindrical
25  use geometry, only: cyclic_x, cyclic_x_pd
26 ! use geometry, only: COORDINATES
27 
28 ! Global Parameters:
29 !---------------------------------------------------------------------//
30  use param1, only: one, zero, undefined_i, undefined
31 
32 ! Use the error manager for posting error messages.
33 !---------------------------------------------------------------------//
34  use error_manager
35 
36  use toleranc
37 
38  implicit none
39 
40 ! Initialize the error manager.
41  CALL init_err_msg("CHECK_GEOMETRY_PREREQS")
42 
43 ! Verify that the domain decomposition was specified.
44  IF(imax == undefined_i .OR. jmax == undefined_i .OR. &
45  (.NOT.no_k .AND. kmax == undefined_i) ) THEN
46  WRITE(err_msg,1000)
47  CALL flush_err_msg(abort=.true.)
48  ENDIF
49 
50  1000 FORMAT('Error 1000: IMAX or JMAX or KMAX not specified in ', &
51  'mfix.dat')
52 
53 ! If no variation in a direction is considered, the number of cells in
54 ! that direction should be 1
55  IF(no_i) THEN
56  WRITE(err_msg, 1100) 'I','I','east and west'
57  CALL flush_err_msg(abort=.true.)
58  ENDIF
59 
60  IF(no_j) THEN
61  WRITE(err_msg, 1100) 'J','J','north and south'
62  CALL flush_err_msg(abort=.true.)
63  ENDIF
64 
65  1100 FORMAT('Error 1100: Illegal geometry: NO_',a1,' is disabled. ', &
66  'The same functionality',/'is achieved with one cell (',a1, &
67  'MAX=1) and making the ',a,' walls',/'free-slip. Please ', &
68  'correct the mfix.dat file.')
69 
70  IF (xmin < zero) THEN
71  WRITE(err_msg, 1101) 'XMIN'
72  CALL flush_err_msg(abort=.true.)
73  ENDIF
74 
75  1101 FORMAT('Error 1101: Illegal geometry: ',a,' cannot be less ', &
76  'than zero.',/'Please correct the mfix.dat file.')
77 
78 
79  SELECT CASE(trim(coordinates))
80  CASE ('CYLINDRICAL')
81  cylindrical = .true.
82  IF(cyclic_x .OR. cyclic_x_pd) THEN
83  WRITE(err_msg, 1102)
84  CALL flush_err_msg(abort=.true.)
85  ENDIF
86 
87  1102 FORMAT('Error 1102: X-axis cannot be CYCLIC in cylindrical ', &
88  'coordinates',/'Please correct the mfix.dat file.')
89 
90  CASE ('CARTESIAN')
91  cylindrical = .false.
92 
93  CASE DEFAULT
94  WRITE(err_msg, 1103)
95  CALL flush_err_msg(abort=.true.)
96 
97  1103 FORMAT('Error 1103: Unknown COORDINATES specified. Please ', &
98  'correct the ',/'mfix.dat file.')
99 
100  END SELECT
101 
102 
103  IF(no_k) THEN
104  IF(kmax == undefined_i) THEN
105  kmax = 1
106  ELSEIF(kmax /= 1) THEN
107  WRITE(err_msg, 1110) 'KMAX','NO_K'
108  CALL flush_err_msg(abort=.true.)
109  ENDIF
110 
111  1110 FORMAT('Error 1110: Illegal geometry: ',a,' must remain ', &
112  'UNDEFINED_I or 1 when',/a,' is TRUE. Please correct the ', &
113  'mfix.dat file.')
114 
115  IF(dz(1)==undefined) THEN
116  IF(zlength==undefined) THEN
117  IF(cylindrical) THEN
118  dz(1) = 8.*atan(one)
119  zlength = 8.*atan(one)
120  ELSE
121  dz(1) = one
122  zlength = one
123  ENDIF
124  ELSE
125  dz(1) = zlength
126  ENDIF
127  ELSE
128  IF(zlength==undefined) THEN
129  zlength = dz(1)
130  ELSE
131  IF(.NOT.compare(zlength,dz(1)))THEN
132  WRITE(err_msg, 1111) 'DZ(1) and ZLENGTH'
133  CALL flush_err_msg(abort=.true.)
134  ENDIF
135 
136  1111 FORMAT('Error 1111: Illegal geometry: ',a,' are not equal.',/ &
137  'Please correct the mfix.dat file.')
138 
139  ENDIF
140  ENDIF
141  ENDIF
142 
143  CALL finl_err_msg
144 
145  RETURN
146 
147 
148 
149  END SUBROUTINE check_geometry_prereqs
character(len=16) coordinates
Definition: geometry_mod.f:17
subroutine finl_err_msg
logical function compare(V1, V2)
Definition: toleranc_mod.f:94
logical no_i
Definition: geometry_mod.f:20
double precision, parameter one
Definition: param1_mod.f:29
subroutine check_geometry_prereqs
double precision, parameter undefined
Definition: param1_mod.f:18
double precision, dimension(0:dim_k) dz
Definition: geometry_mod.f:72
integer imax
Definition: geometry_mod.f:47
subroutine init_err_msg(CALLER)
logical cyclic_x
Definition: geometry_mod.f:149
integer kmax
Definition: geometry_mod.f:51
logical no_k
Definition: geometry_mod.f:28
logical cyclic_x_pd
Definition: geometry_mod.f:155
logical no_j
Definition: geometry_mod.f:24
logical cylindrical
Definition: geometry_mod.f:168
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
double precision xmin
Definition: geometry_mod.f:75
integer jmax
Definition: geometry_mod.f:49
double precision, parameter zero
Definition: param1_mod.f:27
double precision zlength
Definition: geometry_mod.f:37
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)