MFIX  2016-1
set_phase_index.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: SET_PHASE_INDEX !
4 ! !
5 ! Purpose: Set the index of all particles based on their diameter and !
6 ! density. !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  SUBROUTINE set_phase_index
10 
11 ! Modules
12 !---------------------------------------------------------------------//
13  use discretelement, only: pijk
14  USE discretelement, only: des_radius, ro_sol
15  USE discretelement, only: des_mmax
16  USE discretelement, only: max_pip
17  USE functions, only: is_nonexistent, is_ghost, is_entering_ghost
18  USE functions, only: is_exiting_ghost
19  USE error_manager
21  use mpi_utility
22  use param1, only: small_number
23  USE physprop, only: mmax, d_p0, ro_s0
24  USE run, only: run_type, solids_model
25  USE run, only: any_species_eq
26  use sendrecv
27  IMPLICIT NONE
28 
29 ! Local Variables
30 !---------------------------------------------------------------------//
31 ! particle no.
32  INTEGER :: L
33 ! solids phase no.
34  INTEGER :: M
35 ! May need to offset index when using d_p0 and ro_s
36  INTEGER :: DM
37 ! IER for error reporting
38  INTEGER :: IER
39 ! Difference between a particles diameter (density) and the diameter
40 ! (density) of a phase specified in the data file.
41  DOUBLE PRECISION dDp, dRho
42 !......................................................................!
43 
44 
45 ! The restart file contains the phase index for reacting cases as the
46 ! diameter and/or density of the particle may have changed.
47  IF(run_type /= 'NEW' .AND. any_species_eq) RETURN
48 
49 ! Initialize the error flag.
50  ier = 0
51 
52 ! solids phase index of particle.
53 ! ---------------------------------------------------------------->>>
54  DO l = 1, max_pip
55  IF(is_nonexistent(l)) cycle
56  IF(is_ghost(l) .OR. is_entering_ghost(l) .OR. is_exiting_ghost(l)) cycle
57 
58 ! Determining the solids phase of each particle by matching the diameter
59 ! and density to those specified in the data file.
60  m_lp: DO m = mmax+1, mmax+des_mmax
61  ddp = abs(2.0d0*des_radius(l)-d_p0(m))
62  drho = abs( ro_sol(l)-ro_s0(m))
63  IF( ddp < small_number .AND. drho < small_number) THEN
64  pijk(l,5) = m
65  EXIT m_lp
66  ENDIF
67  ENDDO m_lp
68 ! Flag error if no match is found.
69  IF(pijk(l,5).EQ.0) ier = 1
70  ENDDO
71 
72 ! Sync up the error flag across all processes.
73  CALL global_all_sum(ier)
74  IF(ier == 0) RETURN
75 
76 ! Point of no return: Report errors and abort
77 !----------------------------------------------------------------------
78  CALL init_err_msg("SET_PHASE_INDEX")
79 
80  CALL open_pe_log(ier)
81 
82  WRITE(err_msg, 1100)
83  CALL flush_err_msg(footer=.false.)
84 
85  1100 FORMAT('Error 1100: Unable to determine the phase of one or ',&
86  'more particles.',/8x,'ID',4x,'Diameter',6x,'Density',/)
87 
88  DO l = 1, max_pip
89 ! skipping particles that do not exist
90  IF(is_nonexistent(l)) cycle
91  IF(is_ghost(l) .OR. is_entering_ghost(l) .OR. is_exiting_ghost(l)) cycle
92 
93 ! Flag as an error if no match is found.
94  IF(pijk(l,5).EQ.0) THEN
95  WRITE(err_msg,9000) l, 2.0*des_radius(l), ro_sol(l)
96  CALL flush_err_msg(header=.false., footer=.false.)
97  ENDIF
98  ENDDO
99 
100  WRITE(err_msg, 1101)
101  CALL flush_err_msg(header=.false., footer=.false.)
102 
103  1101 FORMAT(' ',/'Defined phase parameters from mfix.dat:',/3x,'ID',&
104  5x,'Diameter',5x,'Density')
105 
106  DO m = mmax+1, des_mmax+mmax
107  WRITE(err_msg, 9000) m, d_p0(m), ro_s0(m)
108  CALL flush_err_msg(header=.false., footer=.false.)
109  ENDDO
110 
111  WRITE(err_msg, 1102)
112  CALL flush_err_msg(header=.false., abort=.true.)
113 
114  1102 FORMAT('Please correct the mfix.dat or particle_input.dat files.')
115 
116  9000 FORMAT(i10,2(2x,g12.5))
117 
118  END SUBROUTINE set_phase_index
double precision, dimension(dim_m) d_p0
Definition: physprop_mod.f:25
subroutine set_phase_index
subroutine des_par_exchange()
character(len=3), dimension(dim_m) solids_model
Definition: run_mod.f:253
subroutine init_err_msg(CALLER)
integer mmax
Definition: physprop_mod.f:19
double precision, parameter small_number
Definition: param1_mod.f:24
character(len=16) run_type
Definition: run_mod.f:33
logical any_species_eq
Definition: run_mod.f:118
Definition: run_mod.f:13
character(len=line_length), dimension(line_count) err_msg
double precision, dimension(dim_m) ro_s0
Definition: physprop_mod.f:28
subroutine open_pe_log(IER)
Definition: open_files.f:270
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)