49 LOGICAL :: RECOGNIZED_BC_TYPE
61 bc_defined(bcv) = .false.
62 IF(bc_x_w(bcv) /=
undefined) bc_defined(bcv) = .true.
63 IF(bc_x_e(bcv) /=
undefined) bc_defined(bcv) = .true.
64 IF(bc_y_s(bcv) /=
undefined) bc_defined(bcv) = .true.
65 IF(bc_y_n(bcv) /=
undefined) bc_defined(bcv) = .true.
68 IF(bc_i_w(bcv) /=
undefined_i) bc_defined(bcv) = .true.
69 IF(bc_i_e(bcv) /=
undefined_i) bc_defined(bcv) = .true.
70 IF(bc_j_s(bcv) /=
undefined_i) bc_defined(bcv) = .true.
71 IF(bc_j_n(bcv) /=
undefined_i) bc_defined(bcv) = .true.
74 IF(bc_type(bcv) ==
'CG_NSW') bc_defined(bcv) = .true.
75 IF(bc_type(bcv) ==
'CG_FSW') bc_defined(bcv) = .true.
76 IF(bc_type(bcv) ==
'CG_PSW') bc_defined(bcv) = .true.
77 IF(bc_type(bcv) ==
'CG_MI') bc_defined(bcv) = .true.
78 IF(bc_type(bcv) ==
'CG_PO') bc_defined(bcv) = .true.
80 IF (bc_type(bcv) ==
'DUMMY') bc_defined(bcv) = .false.
82 IF(bc_type(bcv)/=
undefined_c .AND. bc_type(bcv)/=
'DUMMY')
THEN 84 recognized_bc_type = .false.
86 valid_bc_type(i) = trim(valid_bc_type(i))
87 IF(valid_bc_type(i) == trim(bc_type(bcv)))
THEN 88 bc_type_enum(bcv) = valid_bc_type_enum(i)
89 recognized_bc_type = .true.
94 IF(.NOT.recognized_bc_type)
THEN 96 bc_type_enum(bcv), valid_bc_type
101 IF(.NOT.bc_defined(bcv)) cycle
102 IF(is_cg(bc_type_enum(bcv))) cycle
108 WRITE(
err_msg,1101) bcv,
'BC_X_w and BC_I_w' 115 bc_x_e(bcv) = xlength
117 WRITE(
err_msg, 1101) bcv,
'BC_X_e and BC_I_e' 126 WRITE(
err_msg, 1101) bcv,
'BC_Y_s and BC_J_s' 133 bc_y_n(bcv) = ylength
135 WRITE(
err_msg, 1101) bcv,
'BC_Y_n and BC_J_n' 144 WRITE(
err_msg, 1101) bcv,
'BC_Z_b and BC_K_b' 153 WRITE(
err_msg, 1101) bcv,
'BC_Z_t and BC_K_t' 158 1101
FORMAT(
'Error 1101: Boundary condition ',i3,
' is ill-defined.',/ &
159 a,
' are not specified.',/
'Please correct the mfix.dat file.')
163 valid_bc_type(i) = trim(valid_bc_type(i))
164 IF(valid_bc_type(i) == bc_type(bcv))
THEN 165 IF(mod(i,2) == 0)
THEN 166 bc_type_enum(bcv) = valid_bc_type_enum(i-1)
168 bc_type_enum(bcv) = valid_bc_type_enum(i)
175 bc_type_enum(bcv), valid_bc_type
185 1100
FORMAT(
'Error 1100: Illegal entry: ',a,
' = ',a,/
'Valid entries:',&
186 ' ',10(/5x,a,2x,a),/5x,a)
232 INTEGER,
INTENT(in) :: BCV
237 INTEGER :: I_w , I_e , J_s , J_n , K_b , K_t
255 CALL calc_cell (xmin, bc_x_w(bcv), dx, imax, i_w)
257 CALL calc_cell (xmin, bc_x_e(bcv), dx, imax, i_e)
259 IF(bc_x_w(bcv) == bc_x_e(bcv))
THEN 260 IF(
compare(bc_x_w(bcv),xmin))
THEN 263 ELSEIF(
compare(bc_x_w(bcv),xmin+xlength))
THEN 292 IF(bc_y_s(bcv) == bc_y_n(bcv))
THEN 296 ELSE IF (
compare(bc_y_s(bcv),ylength))
THEN 348 IF (bc_j_s(bcv)<1 .OR. bc_j_s(bcv)>jmax2) ier = 1
349 IF (bc_i_w(bcv)<1 .OR. bc_i_w(bcv)>imax2) ier = 1
351 IF (bc_j_n(bcv)<1 .OR. bc_j_n(bcv)>jmax2) ier = 1
352 IF (bc_i_e(bcv)<1 .OR. bc_i_e(bcv)>imax2) ier = 1
354 IF (bc_j_s(bcv) > bc_j_n(bcv)) ier = 1
355 IF (bc_i_w(bcv) > bc_i_e(bcv)) ier = 1
359 'X', bc_x_w(bcv), bc_x_e(bcv),
'I',bc_i_w(bcv),bc_i_e(bcv), &
360 'Y', bc_y_s(bcv), bc_y_n(bcv),
'J',bc_j_s(bcv),bc_j_n(bcv), &
365 1100
FORMAT(
'Error 1100: Invalid location specified for BC ',i3,
'.', &
366 3(/3x,a1,
': ',g12.5,
',',g12.5,8x,a1,
': ',i8,
',',i8),/ &
367 'Please correct the mfix.dat file.')
415 INTEGER,
INTENT(in) :: BCV
420 INTEGER :: I_w, I_e, J_s, J_n, K_b, K_t
428 LOGICAL :: X_CONSTANT, Y_CONSTANT, Z_CONSTANT
441 CALL calc_cell (xmin, bc_x_w(bcv), dx, imax, i_w)
442 CALL calc_cell (xmin, bc_x_e(bcv), dx, imax, i_e)
443 IF (bc_x_w(bcv) /= bc_x_e(bcv))
THEN 455 CALL calc_loc (xmin,dx,bc_i_w(bcv),bc_x_w(bcv))
457 CALL calc_loc (xmin,dx,bc_i_e(bcv),bc_x_e(bcv))
458 IF(bc_x_w(bcv) /= bc_x_e(bcv)) x_constant = .false.
470 IF(bc_y_s(bcv) /= bc_y_n(bcv))
THEN 485 IF (bc_y_s(bcv) /= bc_y_n(bcv)) y_constant = .false.
525 y_constant, z_constant, bcv,
'BC')
530 IF(bc_i_w(bcv)<1 .OR. bc_i_w(bcv)>imax2) ier = 1
531 IF(bc_i_e(bcv)<1 .OR. bc_i_e(bcv)>imax2) ier = 1
532 IF(bc_j_s(bcv)<1 .OR. bc_j_s(bcv)>jmax2) ier = 1
533 IF(bc_j_n(bcv)<1 .OR. bc_j_n(bcv)>jmax2) ier = 1
537 IF(bc_j_s(bcv) > bc_j_n(bcv)) ier = 1
538 IF(bc_i_w(bcv) > bc_i_e(bcv)) ier = 1
542 'X', bc_x_w(bcv), bc_x_e(bcv),
'I',bc_i_w(bcv),bc_i_e(bcv), &
543 'Y', bc_y_s(bcv), bc_y_n(bcv),
'J',bc_j_s(bcv),bc_j_n(bcv), &
548 1100
FORMAT(
'Error 1100: Invalid location specified for BC ',i3,
'.', &
549 3(/3x,a1,
': ',g12.5,
',',g12.5,8x,a1,
': ',i8,
',',i8),/ &
550 'Please correct the mfix.dat file.')
integer, dimension(dimension_bc) bc_k_b
double precision, dimension(dimension_bc) bc_y_n
subroutine calc_cell(RMIN, REACTOR_LOC, D_DIR, N_DIR, CELL_LOC)
character(len=32) function ivar(VAR, i1, i2, i3)
logical function compare(V1, V2)
subroutine check_bc_geometry
subroutine check_plane(X_CONSTANT, Y_CONSTANT, Z_CONSTANT, BC, NAM
integer, dimension(dimension_bc) bc_i_w
integer, dimension(dimension_bc) bc_j_n
double precision, dimension(0:dim_j) dy
integer, parameter dimension_bc
double precision, dimension(dimension_bc) bc_x_e
double precision, parameter undefined
double precision, dimension(0:dim_k) dz
double precision, dimension(dimension_bc) bc_y_s
subroutine init_err_msg(CALLER)
integer, dimension(dimension_bc) bc_k_t
integer, dimension(dimension_bc) bc_j_s
logical, dimension(dimension_bc) bc_defined
double precision, dimension(0:dim_i) dx
subroutine check_bc_geometry_flow(BCV)
subroutine location_check(CELL_SPECIFIED, CELL_CALCULATED, COUNTER, MESSAGE)
subroutine check_bc_geometry_wall(BCV)
double precision, dimension(dimension_bc) bc_z_b
integer, parameter undefined_i
character(len=line_length), dimension(line_count) err_msg
double precision, dimension(dimension_bc) bc_z_t
integer, dimension(dimension_bc) bc_i_e
double precision, parameter zero
subroutine calc_loc(RMIN, D_DIR, CELL_LOC, REACTOR_LOC)
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
double precision, dimension(dimension_bc) bc_x_w
character, parameter undefined_c