MFIX  2016-1
des_thermo_newvalues.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Module name: DES_THERMO_NEWVALUES !
4 ! !
5 ! Purpose: !
6 ! !
7 ! !
8 ! Author: J.Musser Date: 16-Jun-10 !
9 ! !
10 ! Comments: !
11 ! !
12 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
13  SUBROUTINE des_thermo_newvalues
14 
15  USE compar
16  Use des_thermo
17  Use des_rxns
18  Use discretelement
19  USE geometry
20  USE indices
21  Use param1
22  Use physprop
23  use run, only: energy_eq
24  use functions
25  use funits, only: dmp_log
26  use run, only: any_species_eq
27  USE des_thermo_cond, only: des_qw_cond
28  IMPLICIT NONE
29 
30 ! Passed variables
31 !-----------------------------------------------
32 ! NONE
33 
34 ! Local variables
35 !---------------------------------------------------------------------//
36 ! Index of neighbor particle of particle I such that I < J
37  INTEGER IJK
38 ! Loop index for particles.
39  INTEGER NP, lNP
40 ! Logical for Adams-Bashfort integration.
41  LOGICAL,SAVE:: FIRST_PASS = .true.
42 !---------------------------------------------------------------------//
43 
44  IF(.NOT.energy_eq) RETURN
45 
46 ! Second-order Adams-Bashforth scheme defaults to Euler on first pass.
47  IF(first_pass .AND. intg_adams_bashforth) THEN
48  WHERE(particle_state(:max_pip) == normal_particle) &
49  q_source0(:max_pip) = q_source(:max_pip)/ &
50  (pmass(:max_pip)*des_c_ps(:max_pip))
51  ENDIF
52  first_pass = .false.
53 
54 ! First-order method
55  IF (intg_euler) THEN
56  WHERE(particle_state(:max_pip) == normal_particle) &
57  des_t_s(:max_pip) = des_t_s(:max_pip) + &
58  dtsolid*(q_source(:max_pip)/(pmass(:max_pip)* &
59  des_c_ps(:max_pip)))
60 
61 ! Second-order Adams-Bashforth scheme
62  ELSE
63  WHERE(particle_state(:max_pip) == normal_particle)
64  des_t_s(:max_pip) = des_t_s(:max_pip) + dtsolid * &
65  (1.5d0*q_source(:max_pip) -0.5d0*q_source0(:max_pip))/ &
66  (pmass(:max_pip)*des_c_ps(:max_pip))
67  q_source0(:max_pip) = q_source(:max_pip)
68  ENDWHERE
69  ENDIF
70 
71 
72  q_source(:) = zero
73  IF(ALLOCATED(des_qw_cond)) &
74  des_qw_cond(:,:) = zero
75 
76 ! Update particle from reactive chemistry process.
77  IF(any_species_eq .AND. .NOT.des_explicitly_coupled)&
79 
80  RETURN
81 
82  END SUBROUTINE des_thermo_newvalues
logical dmp_log
Definition: funits_mod.f:6
double precision, dimension(:), allocatable des_t_s
double precision, dimension(:), allocatable q_source0
subroutine des_thermo_newvalues
logical any_species_eq
Definition: run_mod.f:118
Definition: run_mod.f:13
logical energy_eq
Definition: run_mod.f:100
double precision, dimension(:), allocatable q_source
double precision, dimension(:,:), allocatable des_qw_cond
subroutine des_reaction_model
double precision, parameter zero
Definition: param1_mod.f:27
double precision, dimension(:), allocatable des_c_ps