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