File: /nfs/home/0/users/jenkins/mfix.git/model/des/calc_thermo_des.f

1     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2     !                                                                      !
3     !  Module name: CALC_THERMO_DES                                        !
4     !                                                                      !
5     !  Purpose:                                                            !
6     !                                                                      !
7     !                                                                      !
8     !  Author: J.Musser                                   Date: 16-Jun-10  !
9     !                                                                      !
10     !  Comments:                                                           !
11     !                                                                      !
12     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
13           SUBROUTINE CALC_THERMO_DES
14     
15           use physprop, only: SMAX
16           use physprop, only: K_s0
17     
18           USE compar
19           USE des_rxns
20           USE des_thermo
21           USE discretelement
22           USE fldvar
23           USE functions
24           USE geometry
25           USE indices
26           USE interpolation
27           USE param1
28           USE run
29     
30           IMPLICIT NONE
31     
32     ! Local variables
33     !---------------------------------------------------------------------//
34     ! Index of neighbor particle of particle I such that I < J
35           INTEGER IJK
36     ! Loop index for particles.
37           INTEGER NP, lNP
38     ! Phase index for particle NP
39           INTEGER M
40     ! Identifies that the indicated particle is of interest for debugging
41           LOGICAL FOCUS
42     ! Variables needed for calculating new interpolation quantities for
43     ! species and energy equations
44           INTEGER INTERP_IJK(2**3)
45           DOUBLE PRECISION INTERP_WEIGHTS(2**3)
46     
47     ! Functions
48     !---------------------------------------------------------------------//
49     
50     ! This is a quick work-around to keep the thermo routines from causes
51     ! issues while the "check_data" routines are rewritten. Moving forward
52     ! this routine should be split apart to avoid the particle loops for
53     ! cold-flow, non-reacting cases.
54           IF(.NOT.ENERGY_EQ .AND. .NOT.ANY_SPECIES_EQ) RETURN
55     
56     ! Loop over fluid cells.
57     !---------------------------------------------------------------------//
58           IJK_LP: DO IJK = IJKSTART3, IJKEND3
59              IF(.NOT.FLUID_AT(IJK)) CYCLE IJK_LP
60              IF(PINC(IJK) == 0) CYCLE IJK_LP
61     
62     ! Interpolation: Removed J.Musser 11/8/2012
63     !---------------------------------------------------------------------//
64     !     IF(DES_INTERP_ON .AND. (ANY_SPECIES_EQ .OR. DES_CONV_EQ)) THEN
65     !         INTERP_IJK(:) = -1
66     !         INTERP_WEIGHTS(:) = ZERO
67     !         CALL INTERPOLATE_CC(NP, INTERP_IJK, INTERP_WEIGHTS, FOCUS)
68     !      ENDIF
69     
70     ! Preform user-defined calculations from fluid grid.
71              IF(CALL_USR) CALL USR4_DES(IJK)
72     
73     ! Loop over all particles in cell IJK.
74     !---------------------------------------------------------------------//
75              lNP_LP: DO lNP = 1, PINC(IJK)
76                 NP = PIC(IJK)%p(lNP)
77     
78     ! Skip indices that do not represent particles
79                 IF(.NOT.PEA(NP,1)) CYCLE lNP_LP
80                 IF(any(PEA(NP,2:4))) CYCLE lNP_LP
81     
82     ! Reset the debug flag
83                 FOCUS = .FALSE.
84     
85     ! Calculate time dependent physical properties
86                 CALL DES_PHYSICAL_PROP(NP, FOCUS)
87     
88     ! Identify the solid phases of each particle
89                 M = PIJK(NP,5)
90     
91     ! calculate heat transfer via convection
92                 IF(CALC_CONV_DES) CALL DES_CONVECTION(NP, M, IJK, &
93                    INTERP_IJK, INTERP_WEIGHTS, FOCUS)
94     
95     ! calculate heat transfer via radiation
96                 IF(CALC_RADT_DES(M)) CALL DES_RADIATION(NP, M, IJK, FOCUS)
97     
98     ! Calculate reaction rates and interphase mass transfer
99                 IF(ANY_SPECIES_EQ) CALL DES_RRATES0(NP, M, IJK, &
100                    INTERP_IJK, INTERP_WEIGHTS, FOCUS)
101     
102              ENDDO lNP_LP ! End loop over all particles
103           ENDDO IJK_LP ! End loop over fluid cells
104     
105           END SUBROUTINE CALC_THERMO_DES
106