MFIX  2016-1
mod_bc_i.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Subroutine: MOD_BC_I C
4 ! Author: P. Nicoletti Date: 10-DEC-91 C
5 ! C
6 ! Purpose: modify the "I" values for the b.c. plane C
7 ! This is a yz plane C
8 ! C
9 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
10  SUBROUTINE mod_bc_i(BCV)
11 
12  use bc, only: bc_i_w, bc_i_e
13  use bc, only: bc_j_s, bc_j_n
14  use bc, only: bc_k_b, bc_k_t
15  use bc, only: bc_plane
16 
17  USE geometry, only: icbc_flag
18 
19  USE compar
20  USE mpi_utility
21 
22  use error_manager
23  USE functions
24 
25  IMPLICIT NONE
26 
27 !-----------------------------------------------
28 ! Dummy arguments
29 !-----------------------------------------------
30 ! boundary condition index
31  INTEGER, INTENT(IN) :: BCV
32 
33 ! i cell indices defining location of yz plane
34  INTEGER :: I_w, I_e
35 ! south/bottom j,k cell indices of yz plane
36  INTEGER :: J_s, K_b
37 
38 !-----------------------------------------------
39 ! Local variables
40 !-----------------------------------------------
41 ! 'IJK' indices
42  INTEGER :: OWNER
43  INTEGER :: J, K
44  INTEGER :: IJK , IPJK
45 
46  INTEGER :: IER
47  LOGICAL :: ERROR
48  INTEGER :: I_FLUID, IJK_FLUID
49  INTEGER :: I_WALL, IJK_WALL
50 
51  CALL init_err_msg("MOD_BC_I")
52 
53  i_w = bc_i_w(bcv)
54  i_e = bc_i_e(bcv)
55 
56  j_s = bc_j_s(bcv)
57  k_b = bc_k_b(bcv)
58 
59 ! Establish the OWNER of the BC
60  owner = merge(mype, 0, is_on_mype_owns(i_w, j_s, k_b))
61  CALL global_all_sum(owner)
62 
63  IF(mype == owner) THEN
64 
65  ijk = funijk(i_w, j_s, k_b)
66  ipjk = funijk(i_w+1, j_s, k_b)
67 
68 ! Flow on west boundary (fluid cell on east).
69  IF(wall_icbc_flag(ijk) .AND. icbc_flag(ipjk)(1:1)=='.') THEN
70  i_w = i_w
71  i_e = i_e
72  bc_plane(bcv) = 'E'
73 
74 ! Flow on east boundary (fluid cell on west).
75  ELSEIF(wall_icbc_flag(ipjk) .AND. icbc_flag(ijk)(1:1)=='.') THEN
76  i_w = i_w + 1
77  i_e = i_e + 1
78  bc_plane(bcv) = 'W'
79 
80 ! Set the plane of a value we know to be wrong so we can detect the error.
81  ELSE
82  bc_plane(bcv) = '.'
83  ENDIF
84  ENDIF
85 
86 ! The owner distributes the new Iw/Ie coordinates to the other ranks.
87  CALL bcast(i_w, owner)
88  CALL bcast(i_e, owner)
89  CALL bcast(bc_plane(bcv), owner)
90 
91 
92 ! If there is an error, send IJK/IPJK to all ranks. Report and exit.
93  IF(bc_plane(bcv) == '.') THEN
94  CALL bcast(ipjk,owner)
95  CALL bcast(ijk, owner)
96 
97  WRITE(err_msg, 1100) bcv, i_w, i_e, j_s, k_b, &
98  ijk, icbc_flag(ijk), ipjk, icbc_flag(ipjk)
99  CALL flush_err_msg(abort=.true.)
100  ENDIF
101 
102  1100 FORMAT('Error 1100: Cannot locate flow plane for boundary ', &
103  'condition ',i3,'.',2/3x,'I West = ',i6,' I East = ',i6,/&
104  3x,'J South = ',i6,' K Bottom = ',i6,2/' The following ', &
105  'should conttain a wall cell and fluid cell:',/3x,'IJK ',i9, &
106  ' :: ',a3,/3x,'IPJK ',i9,' :: ',a3,2/' Maybe no IC was ', &
107  'specified for the fluid cell.')
108 
109 ! Store the new values in the global data array.
110  bc_i_w(bcv) = i_w
111  bc_i_e(bcv) = i_e
112 
113 ! Set up the I-indices for checking the entire BC region.
114  i_wall = bc_i_w(bcv)
115  i_fluid = merge(i_wall-1, i_wall+1, bc_plane(bcv)=='W')
116 
117 
118 ! First pass through all of the BC region and verify that you have
119 ! inflow/outflow specified against a wall. Flag any errors.
120  error = .false.
121  DO k = bc_k_b(bcv), bc_k_t(bcv)
122  DO j = bc_j_s(bcv), bc_j_n(bcv)
123 
124  IF(.NOT.is_on_mype_plus2layers(i_fluid,j,k)) cycle
125  IF(.NOT.is_on_mype_plus2layers(i_wall, j,k)) cycle
126  IF(dead_cell_at(i_fluid,j,k)) cycle
127  IF(dead_cell_at(i_wall, j,k)) cycle
128 
129  ijk_wall = funijk(i_wall,j,k)
130  ijk_fluid = funijk(i_fluid,j,k)
131 
132 ! Verify that the the fluid and wall cells match the ICBC_FLAG.
133  IF(.NOT.(wall_icbc_flag(ijk_wall) .AND. &
134  icbc_flag(ijk_fluid)(1:1) == '.')) error = .true.
135 
136  ENDDO
137  ENDDO
138 
139 ! Sync up the error flag across all processes.
140  CALL global_all_or(error)
141 
142 ! If an error is detected, have each rank open a log file and write
143 ! it's own message. Otherwise, we need to send all the data back to
144 ! PE_IO and that's too much work!
145  IF(error) THEN
146 
147  CALL open_pe_log(ier)
148 
149  WRITE(err_msg, 1200) bcv
150  CALL flush_err_msg(footer=.false.)
151 
152  DO k = bc_k_b(bcv), bc_k_t(bcv)
153  DO j = bc_j_s(bcv), bc_j_n(bcv)
154 
155  IF(.NOT.is_on_mype_plus2layers(i_fluid,j,k)) cycle
156  IF(.NOT.is_on_mype_plus2layers(i_wall, j,k)) cycle
157  IF(dead_cell_at(i_fluid,j,k)) cycle
158  IF(dead_cell_at(i_wall, j,k)) cycle
159 
160  ijk_wall = funijk(i_wall,j,k)
161  ijk_fluid = funijk(i_fluid,j,k)
162 
163  IF(.NOT.(wall_icbc_flag(ijk_wall) .AND. &
164  icbc_flag(ijk_fluid)(1:1) == '.')) THEN
165 
166  WRITE(err_msg, 1201) &
167  i_wall, j, k, ijk_wall, icbc_flag(ijk_wall), &
168  i_fluid, j, k, ijk_fluid, icbc_flag(ijk_fluid)
169  CALL flush_err_msg(header=.false., footer=.false.)
170  ENDIF
171  ENDDO
172  ENDDO
173 
174  WRITE(err_msg,"('Please correct the mfix.dat file.')")
175  CALL flush_err_msg(header=.false., abort=.true.)
176 
177  ENDIF
178 
179 
180  1200 FORMAT('Error 1200: Illegal geometry for boundary condition:',i3)
181 
182  1201 FORMAT(' ',/14x,'I',7x,'J',7x,'K',7x,'IJK',4x,'FLAG',/3x, &
183  'WALL ',3(2x,i6),2x,i9,3x,a,/3x,'FLUID',3(2x,i6),2x,i9,3x,a)
184 
185 
186  CALL finl_err_msg
187 
188  RETURN
189  END SUBROUTINE mod_bc_i
190 
integer, dimension(dimension_bc) bc_k_b
Definition: bc_mod.f:70
subroutine finl_err_msg
subroutine mod_bc_i(BCV)
Definition: mod_bc_i.f:11
integer, dimension(dimension_bc) bc_i_w
Definition: bc_mod.f:54
integer, dimension(dimension_bc) bc_j_n
Definition: bc_mod.f:66
character(len=3), dimension(:), pointer icbc_flag
Definition: geometry_mod.f:111
character, dimension(dimension_bc) bc_plane
Definition: bc_mod.f:217
subroutine init_err_msg(CALLER)
integer, dimension(dimension_bc) bc_k_t
Definition: bc_mod.f:74
logical, dimension(:,:,:), allocatable dead_cell_at
Definition: compar_mod.f:127
integer, dimension(dimension_bc) bc_j_s
Definition: bc_mod.f:62
integer mype
Definition: compar_mod.f:24
character(len=line_length), dimension(line_count) err_msg
subroutine open_pe_log(IER)
Definition: open_files.f:270
integer, dimension(dimension_bc) bc_i_e
Definition: bc_mod.f:58
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
Definition: bc_mod.f:23