MFIX  2016-1
check_axis.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: CHECK_AXIS !
4 ! Author: P. Nicoletti Date: 27-NOV-91 !
5 ! !
6 ! Purpose: check geometry data for one axis !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  SUBROUTINE check_axis(NA, DIMEN, ALENGTH, DA, AXIS, &
10  axis_index, no_ijk, shift)
11 
12 !-----------------------------------------------
13 ! Modules
14 !-----------------------------------------------
15  USE param
16  USE param1
17 ! USE funits
18 
19  use error_manager
20 
21 
22  IMPLICIT NONE
23 !-----------------------------------------------
24 ! Dummy arguments
25 !-----------------------------------------------
26 ! number of axis cells (IMAX,JMAX,KMAX)
27  INTEGER, INTENT(INOUT) :: NA
28 ! maximum number of cells along axis based on domain decomposition
29  INTEGER, INTENT(IN) :: DIMEN
30 ! axis length (XLENGTH,YLENGTH,ZLENGTH)
31  DOUBLE PRECISION, INTENT(INOUT) :: ALENGTH
32 ! flag that specifies whether variation along that axis is
33 ! considered (passed variable for NO_I, NO_J, or NO_K)
34  LOGICAL, INTENT(IN) :: NO_IJK
35 ! shift dx, dy and dz values (true only for new and restart_1 runs)
36  LOGICAL, INTENT(IN) :: SHIFT
37 ! axis checked ('X','Y','Z')
38  CHARACTER, INTENT(IN) :: AXIS
39 ! index associated with AXIS ('I','J','K')
40  CHARACTER, INTENT(IN) :: AXIS_INDEX
41 ! cell sizes (DX,DY,DZ);
42 ! use explicit dimension for DA
43 ! DA should be dimensioned DA(DIMEN) rather than DA(0:DIMEN+1) to be
44 ! able to use the logic from previous versions that assumed DA(1)
45 ! as the first element. An error check has been added to ensure that
46 ! DX, DY and DZ definitions in mfix.dat starts with the zeroth
47 ! element; i.e. DA(1).
48  DOUBLE PRECISION, INTENT(INOUT), DIMENSION(DIMEN) :: DA
49 !-----------------------------------------------
50 ! Local parameters
51 !-----------------------------------------------
52 ! percent error allowed in axis length checks
53  DOUBLE PRECISION, PARAMETER :: PERCENT_ERROR = 1.0
54 !-----------------------------------------------
55 ! Local variables
56 !-----------------------------------------------
57 ! number of items specified from NA, ALENGTH, DA
58  INTEGER :: N_SPECIFIED
59 ! loop counter
60  INTEGER :: LC
61 ! temporary storage
62  DOUBLE PRECISION :: TEMP_STOR, lSUM, lERR
63 !-----------------------------------------------
64 
65 
66  CALL init_err_msg("CHECK_AXIS")
67 
68 ! 0) Ensure that if DA is defined then it starts with DA(1); i.e. DX(0), DY(0) or DZ(0)
69  IF(.NOT.no_ijk)THEN
70  IF( da(2) /= undefined .AND. da(1) == undefined) THEN
71  WRITE(err_msg, 1001) axis
72  CALL flush_err_msg(abort=.true.)
73  ENDIF
74  ENDIF
75 
76  1100 FORMAT('Error 1100: The grid specification must start with D', &
77  a1,'(0)',/'Please correct the mfix.dat file.')
78 
79 ! 1) MAKE SURE AT LEAST TWO OF NA, ALENGTH, DA ARE SPECIFIED
80  n_specified = 0
81  IF (na /= undefined_i) n_specified = n_specified + 1
82  IF (alength /= undefined) n_specified = n_specified + 1
83  IF (da(1) /= undefined) n_specified = n_specified + 1
84  IF (n_specified < 2) THEN
85  WRITE(err_msg, 1101) axis, axis, axis, axis_index
86  CALL flush_err_msg(abort=.true.)
87  ENDIF
88 
89  1101 FORMAT('Error 1101: Insufficient grid information for ',a1,'-', &
90  'axis. You must',/'specify at least two of the following: ', &
91  a1,'LENGTH, D',a1,', and ',a1,'MAX','Please correct the ', &
92  'mfix.dat file.')
93 
94 
95 ! 2) NUMBER OF CELLS NOT SPECIFIED - calculate NA based on
96 ! input that was specified
97  IF(na == undefined_i) THEN
98  IF(no_ijk) THEN
99  na = 1
100  ELSE
101  IF(da(2) == undefined) THEN
102  temp_stor = alength/da(1)
103  na = nint(temp_stor)
104  IF(na - 1 > 0) da(2:na) = da(1)
105  ELSE
106  na = dimen
107  DO lc = 2, dimen
108  IF (da(lc) == undefined) THEN
109  na = lc - 1
110  EXIT
111  ENDIF
112  ENDDO
113  ENDIF
114  ENDIF
115  GO TO 700
116  ENDIF
117 
118 
119  IF(na>=0 .AND. na<=dimen) THEN
120 
121 ! 3) AXIS LENGTH NOT SPECIFIED - calculate ALENGTH based on
122 ! input that was specified
123  IF (alength == undefined) THEN
124  IF(no_ijk) THEN
125  alength = da(1)
126  ELSE
127  IF(da(2) == undefined) THEN
128  IF(na - 1 > 0) da(2:na) = da(1)
129  ENDIF
130  alength = 0.0
131  IF (na > 0) alength = sum(da(:na))
132  ENDIF
133  ENDIF
134 
135 ! 4) CELL SIZE NOT SPECIFIED - calculate NON_VARIABLE DA based on
136 ! input that was specified
137  IF(da(1) == undefined) THEN
138  temp_stor = alength/dble(na)
139  IF(na > 0) da(:na) = temp_stor
140  ENDIF
141 
142 ! 5) ALL 3 SPECIFIED
143  IF(.NOT.no_ijk) THEN
144  IF(da(2) == undefined) THEN
145  IF (na - 1 > 0) da(2:na) = da(1)
146  ENDIF
147  ENDIF
148 
149  ENDIF
150 
151 ! 6) CHECK CONSISTENCY OF AXIS INPUT
152  700 CONTINUE
153 
154 ! This must be a legacy check because the code shouldn't get here
155 ! without exiting and DIMEN is calculated, not a hard-coded param.
156  IF (na<0 .OR. .NOT.no_ijk .AND. na>dimen-2) THEN
157  WRITE(err_msg, 1001) axis_index//'MAX', trim(ival(na))
158  CALL flush_err_msg(abort=.true.)
159  ENDIF
160 
161  IF(alength <= 0.0) THEN
162  WRITE(err_msg, 1001) axis//'LENGTH'
163  CALL flush_err_msg(abort=.true.)
164  ENDIF
165 
166  lsum = 0.0
167  DO lc = 1, na
168  IF (da(lc)<=0.0 .OR. da(lc)==undefined) THEN
169  WRITE(err_msg, 1201) trim(ivar(axis,lc))
170  CALL flush_err_msg(abort=.true.)
171  ENDIF
172  lsum = lsum + da(lc)
173  ENDDO
174 
175  1201 FORMAT('Error 1201: D',a,' is not specified or negative. ', &
176  'Please correct',/'the mfix.dat file.')
177 
178 
179  lerr = 100.0*abs(lsum - alength)/alength
180  IF(lerr > percent_error) THEN
181  WRITE(err_msg,1202) axis, axis, axis, alength, axis, lsum, &
182  lerr, percent_error
183  CALL flush_err_msg(footer=.false.)
184 
185  DO lc = 1, na
186  WRITE(err_msg,"(4x,A,' = ',A)") trim(ivar('D'//axis,lc)), &
187  trim(ival(da(lc)))
188  CALL flush_err_msg(header=.false., footer=.false.)
189  ENDDO
190  WRITE(err_msg,"('Please correct the mfix.dat file')")
191  CALL flush_err_msg(header=.false., abort=.true.)
192  ENDIF
193 
194  1202 FORMAT('Error 1202: ',a1,'LENGTH and sum(D',a1,') are not ', &
195  'consistent.',/3x,a1,'LENGTH = ',g12.5,3x,'sum(D',a1,') = ', &
196  g12.5,/3x,'ERROR = ',g12.5,3x,'ERR TOL = ',g12.5,/' ')
197 
198  DO lc = na + 1, dimen
199  IF(shift .AND. da(lc)/=undefined) THEN
200  WRITE(err_msg, 1205) axis, axis_index
201  CALL flush_err_msg(abort=.true.)
202  ENDIF
203  ENDDO
204 
205  1205 FORMAT('Error 1205: Too many D',a1,' values specified. Only ',a1,&
206  'MAX permitted.',/'Please correct the mfix.dat file.')
207 
208 
209  CALL finl_err_msg
210 
211  RETURN
212 
213 
214  1001 FORMAT('Error 1001: Illegal or unknown input: ',a,' = ',a,/ &
215  'Please correct the mfix.dat file.')
216 
217  END SUBROUTINE check_axis
character(len=32) function ivar(VAR, i1, i2, i3)
subroutine finl_err_msg
subroutine check_axis(NA, DIMEN, ALENGTH, DA, AXIS, AXIS_INDEX, NO_IJK, SHIFT)
Definition: check_axis.f:11
double precision, parameter undefined
Definition: param1_mod.f:18
subroutine init_err_msg(CALLER)
Definition: param_mod.f:2
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)